{-# language CPP #-} module Vulkan.Core10.CommandBufferBuilding ( cmdBindPipeline , cmdSetViewport , cmdSetScissor , cmdSetLineWidth , cmdSetDepthBias , cmdSetBlendConstants , cmdSetDepthBounds , cmdSetStencilCompareMask , cmdSetStencilWriteMask , cmdSetStencilReference , cmdBindDescriptorSets , cmdBindIndexBuffer , cmdBindVertexBuffers , cmdDraw , cmdDrawIndexed , cmdDrawIndirect , cmdDrawIndexedIndirect , cmdDispatch , cmdDispatchIndirect , cmdCopyBuffer , cmdCopyImage , cmdBlitImage , cmdCopyBufferToImage , cmdCopyImageToBuffer , cmdUpdateBuffer , cmdFillBuffer , cmdClearColorImage , cmdClearDepthStencilImage , cmdClearAttachments , cmdResolveImage , cmdSetEvent , cmdResetEvent , cmdWaitEvents , cmdWaitEventsSafe , cmdPipelineBarrier , cmdBeginQuery , cmdUseQuery , cmdEndQuery , cmdResetQueryPool , cmdWriteTimestamp , cmdCopyQueryPoolResults , cmdPushConstants , cmdBeginRenderPass , cmdUseRenderPass , cmdNextSubpass , cmdEndRenderPass , cmdExecuteCommands , ClearRect(..) , ImageSubresourceLayers(..) , BufferCopy(..) , ImageCopy(..) , ImageBlit(..) , BufferImageCopy(..) , ImageResolve(..) , RenderPassBeginInfo(..) , ClearDepthStencilValue(..) , ClearAttachment(..) , ClearColorValue(..) , ClearValue(..) , IndexType(..) , SubpassContents(..) , StencilFaceFlagBits(..) , StencilFaceFlags ) where import Vulkan.CStruct.Utils (FixedArray) import Control.Exception.Base (bracket) import Control.Monad (unless) import Control.Monad.IO.Class (liftIO) import Data.Typeable (eqT) import Foreign.Marshal.Alloc (allocaBytesAligned) import Foreign.Marshal.Alloc (callocBytes) import Foreign.Marshal.Alloc (free) import GHC.IO (throwIO) import GHC.Ptr (castPtr) import GHC.Ptr (nullFunPtr) import Foreign.Ptr (plusPtr) import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Cont (evalContT) import Control.Monad.Trans.Cont (runContT) import qualified Data.Vector (imapM_) import qualified Data.Vector (length) import Foreign.C.Types (CFloat(..)) import Control.Monad.IO.Class (MonadIO) import Data.Type.Equality ((:~:)(Refl)) import Data.Typeable (Typeable) import Foreign.C.Types (CFloat) import Foreign.C.Types (CFloat(CFloat)) import Foreign.Storable (Storable) import Foreign.Storable (Storable(peek)) import Foreign.Storable (Storable(poke)) import qualified Foreign.Storable (Storable(..)) import GHC.Generics (Generic) import GHC.IO.Exception (IOErrorType(..)) import GHC.IO.Exception (IOException(..)) import Data.Int (Int32) import Foreign.Ptr (FunPtr) import Foreign.Ptr (Ptr) import Data.Word (Word32) import Data.Kind (Type) import Control.Monad.Trans.Cont (ContT(..)) import Data.Vector (Vector) import Vulkan.CStruct.Utils (advancePtrBytes) import Vulkan.CStruct.Extends (forgetExtensions) import Vulkan.CStruct.Utils (lowerArrayPtr) import Vulkan.CStruct.Extends (pokeSomeCStruct) import Vulkan.NamedType ((:::)) import Vulkan.Core10.Handles (Buffer) import Vulkan.Core10.Handles (Buffer(..)) import Vulkan.Core10.OtherTypes (BufferMemoryBarrier) import Vulkan.CStruct.Extends (Chain) import Vulkan.Core10.Handles (CommandBuffer) import Vulkan.Core10.Handles (CommandBuffer(..)) import Vulkan.Core10.Handles (CommandBuffer_T) import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlagBits(..)) import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags) import Vulkan.Core10.Handles (DescriptorSet) import Vulkan.Core10.Handles (DescriptorSet(..)) import Vulkan.Dynamic (DeviceCmds(pVkCmdBeginQuery)) import Vulkan.Dynamic (DeviceCmds(pVkCmdBeginRenderPass)) import Vulkan.Dynamic (DeviceCmds(pVkCmdBindDescriptorSets)) import Vulkan.Dynamic (DeviceCmds(pVkCmdBindIndexBuffer)) import Vulkan.Dynamic (DeviceCmds(pVkCmdBindPipeline)) import Vulkan.Dynamic (DeviceCmds(pVkCmdBindVertexBuffers)) import Vulkan.Dynamic (DeviceCmds(pVkCmdBlitImage)) import Vulkan.Dynamic (DeviceCmds(pVkCmdClearAttachments)) import Vulkan.Dynamic (DeviceCmds(pVkCmdClearColorImage)) import Vulkan.Dynamic (DeviceCmds(pVkCmdClearDepthStencilImage)) import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyBuffer)) import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyBufferToImage)) import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyImage)) import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyImageToBuffer)) import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyQueryPoolResults)) import Vulkan.Dynamic (DeviceCmds(pVkCmdDispatch)) import Vulkan.Dynamic (DeviceCmds(pVkCmdDispatchIndirect)) import Vulkan.Dynamic (DeviceCmds(pVkCmdDraw)) import Vulkan.Dynamic (DeviceCmds(pVkCmdDrawIndexed)) import Vulkan.Dynamic (DeviceCmds(pVkCmdDrawIndexedIndirect)) import Vulkan.Dynamic (DeviceCmds(pVkCmdDrawIndirect)) import Vulkan.Dynamic (DeviceCmds(pVkCmdEndQuery)) import Vulkan.Dynamic (DeviceCmds(pVkCmdEndRenderPass)) import Vulkan.Dynamic (DeviceCmds(pVkCmdExecuteCommands)) import Vulkan.Dynamic (DeviceCmds(pVkCmdFillBuffer)) import Vulkan.Dynamic (DeviceCmds(pVkCmdNextSubpass)) import Vulkan.Dynamic (DeviceCmds(pVkCmdPipelineBarrier)) import Vulkan.Dynamic (DeviceCmds(pVkCmdPushConstants)) import Vulkan.Dynamic (DeviceCmds(pVkCmdResetEvent)) import Vulkan.Dynamic (DeviceCmds(pVkCmdResetQueryPool)) import Vulkan.Dynamic (DeviceCmds(pVkCmdResolveImage)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetBlendConstants)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthBias)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthBounds)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetEvent)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetLineWidth)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetScissor)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetStencilCompareMask)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetStencilReference)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetStencilWriteMask)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetViewport)) import Vulkan.Dynamic (DeviceCmds(pVkCmdUpdateBuffer)) import Vulkan.Dynamic (DeviceCmds(pVkCmdWaitEvents)) import Vulkan.Dynamic (DeviceCmds(pVkCmdWriteTimestamp)) import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_group (DeviceGroupRenderPassBeginInfo) import Vulkan.Core10.FundamentalTypes (DeviceSize) import Vulkan.Core10.Handles (Event) import Vulkan.Core10.Handles (Event(..)) import Vulkan.CStruct.Extends (Extends) import Vulkan.CStruct.Extends (Extendss) import Vulkan.CStruct.Extends (Extensible(..)) import Vulkan.Core10.FundamentalTypes (Extent3D) import Vulkan.Core10.Enums.Filter (Filter) import Vulkan.Core10.Enums.Filter (Filter(..)) import Vulkan.Core10.Handles (Framebuffer) import Vulkan.CStruct (FromCStruct) import Vulkan.CStruct (FromCStruct(..)) import Vulkan.Core10.Handles (Image) import Vulkan.Core10.Handles (Image(..)) import Vulkan.Core10.Enums.ImageAspectFlagBits (ImageAspectFlags) import Vulkan.Core10.Enums.ImageLayout (ImageLayout) import Vulkan.Core10.Enums.ImageLayout (ImageLayout(..)) import Vulkan.Core10.OtherTypes (ImageMemoryBarrier) import Vulkan.Core10.ImageView (ImageSubresourceRange) import Vulkan.Core10.Enums.IndexType (IndexType) import Vulkan.Core10.Enums.IndexType (IndexType(..)) import Vulkan.Core10.OtherTypes (MemoryBarrier) import Vulkan.Core10.FundamentalTypes (Offset3D) import Vulkan.Core10.Handles (Pipeline) import Vulkan.Core10.Handles (Pipeline(..)) import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint) import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint(..)) import Vulkan.Core10.Handles (PipelineLayout) import Vulkan.Core10.Handles (PipelineLayout(..)) import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlagBits) import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlagBits(..)) import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlags) import Vulkan.CStruct.Extends (PokeChain) import Vulkan.CStruct.Extends (PokeChain(..)) import Vulkan.Core10.Enums.QueryControlFlagBits (QueryControlFlagBits(..)) import Vulkan.Core10.Enums.QueryControlFlagBits (QueryControlFlags) import Vulkan.Core10.Handles (QueryPool) import Vulkan.Core10.Handles (QueryPool(..)) import Vulkan.Core10.Enums.QueryResultFlagBits (QueryResultFlagBits(..)) import Vulkan.Core10.Enums.QueryResultFlagBits (QueryResultFlags) import Vulkan.Core10.FundamentalTypes (Rect2D) import Vulkan.Core10.Handles (RenderPass) import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer (RenderPassAttachmentBeginInfo) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_sample_locations (RenderPassSampleLocationsBeginInfoEXT) import {-# SOURCE #-} Vulkan.Extensions.VK_QCOM_render_pass_transform (RenderPassTransformBeginInfoQCOM) import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlagBits(..)) import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags) import Vulkan.CStruct.Extends (SomeStruct) import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlagBits(..)) import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlags) import Vulkan.Core10.Enums.StructureType (StructureType) import Vulkan.Core10.Enums.SubpassContents (SubpassContents) import Vulkan.Core10.Enums.SubpassContents (SubpassContents(..)) import Vulkan.CStruct (ToCStruct) import Vulkan.CStruct (ToCStruct(..)) import Vulkan.Core10.Pipeline (Viewport) import Vulkan.Zero (Zero(..)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO)) import Vulkan.Core10.Enums.IndexType (IndexType(..)) import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlagBits(..)) import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlags) import Vulkan.Core10.Enums.SubpassContents (SubpassContents(..)) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdBindPipeline :: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO () -- | vkCmdBindPipeline - Bind a pipeline object to a command buffer -- -- = Description -- -- Once bound, a pipeline binding affects subsequent commands that interact -- with the given pipeline type in the command buffer until a different -- pipeline of the same type is bound to the bind point. Commands that do -- not interact with the given pipeline type /must/ not be affected by the -- pipeline state. -- -- - The pipeline bound to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_COMPUTE' -- controls the behavior of all -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#dispatch dispatching commands>. -- -- - The pipeline bound to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- controls the behavior of all -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing drawing commands>. -- -- - The pipeline bound to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_RAY_TRACING_KHR' -- controls the behavior of -- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdTraceRaysKHR' and -- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdTraceRaysIndirectKHR'. -- -- == Valid Usage -- -- - If @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_COMPUTE', -- the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support compute operations -- -- - If @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS', -- the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - If @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_COMPUTE', -- @pipeline@ /must/ be a compute pipeline -- -- - If @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS', -- @pipeline@ /must/ be a graphics pipeline -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-variableMultisampleRate variable multisample rate> -- feature is not supported, @pipeline@ is a graphics pipeline, the -- current subpass -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-noattachments uses no attachments>, -- and this is not the first call to this function with a graphics -- pipeline after transitioning to the current subpass, then the sample -- count specified by this pipeline /must/ match that set in the -- previous pipeline -- -- - If -- 'Vulkan.Extensions.VK_EXT_sample_locations.PhysicalDeviceSampleLocationsPropertiesEXT'::@variableSampleLocations@ -- is 'Vulkan.Core10.FundamentalTypes.FALSE', and @pipeline@ is a -- graphics pipeline created with a -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT' -- structure having its @sampleLocationsEnable@ member set to -- 'Vulkan.Core10.FundamentalTypes.TRUE' but without -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT' -- enabled then the current render pass instance /must/ have been begun -- by specifying a -- 'Vulkan.Extensions.VK_EXT_sample_locations.RenderPassSampleLocationsBeginInfoEXT' -- structure whose @pPostSubpassSampleLocations@ member contains an -- element with a @subpassIndex@ matching the current subpass index and -- the @sampleLocationsInfo@ member of that element /must/ match the -- @sampleLocationsInfo@ specified in -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT' -- when the pipeline was created -- -- - This command /must/ not be recorded when transform feedback is -- active -- -- - If @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_RAY_TRACING_KHR', -- the 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support compute operations -- -- - If @pipelineBindPoint@ is -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_RAY_TRACING_KHR', -- the @pipeline@ /must/ be a ray tracing pipeline -- -- - The @pipeline@ /must/ not have been created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_LIBRARY_BIT_KHR' -- set -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @pipelineBindPoint@ /must/ be a valid -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value -- -- - @pipeline@ /must/ be a valid 'Vulkan.Core10.Handles.Pipeline' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, or compute operations -- -- - Both of @commandBuffer@, and @pipeline@ /must/ have been created, -- allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device' -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Handles.Pipeline', -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' cmdBindPipeline :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer that the pipeline will be bound -- to. CommandBuffer -> -- | @pipelineBindPoint@ is a -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value -- specifying to which bind point the pipeline is bound. Binding one does -- not disturb the others. PipelineBindPoint -> -- | @pipeline@ is the pipeline to be bound. Pipeline -> io () cmdBindPipeline :: CommandBuffer -> PipelineBindPoint -> Pipeline -> io () cmdBindPipeline commandBuffer :: CommandBuffer commandBuffer pipelineBindPoint :: PipelineBindPoint pipelineBindPoint pipeline :: Pipeline pipeline = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdBindPipelinePtr :: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) vkCmdBindPipelinePtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) pVkCmdBindPipeline (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) vkCmdBindPipelinePtr FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdBindPipeline is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdBindPipeline' :: Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO () vkCmdBindPipeline' = FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO () mkVkCmdBindPipeline FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO ()) vkCmdBindPipelinePtr Ptr CommandBuffer_T -> PipelineBindPoint -> Pipeline -> IO () vkCmdBindPipeline' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (PipelineBindPoint pipelineBindPoint) (Pipeline pipeline) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetViewport :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Viewport -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Viewport -> IO () -- | vkCmdSetViewport - Set the viewport on a command buffer -- -- = Description -- -- The viewport parameters taken from element i of @pViewports@ replace the -- current state for the viewport index @firstViewport@ + i, for i in [0, -- @viewportCount@). -- -- == Valid Usage -- -- - @firstViewport@ /must/ be less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@ -- -- - The sum of @firstViewport@ and @viewportCount@ /must/ be between @1@ -- and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@, -- inclusive -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports> -- feature is not enabled, @firstViewport@ /must/ be @0@ -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports> -- feature is not enabled, @viewportCount@ /must/ be @1@ -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @pViewports@ /must/ be a valid pointer to an array of -- @viewportCount@ valid 'Vulkan.Core10.Pipeline.Viewport' structures -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - @viewportCount@ /must/ be greater than @0@ -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Pipeline.Viewport' cmdSetViewport :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @firstViewport@ is the index of the first viewport whose parameters are -- updated by the command. ("firstViewport" ::: Word32) -> -- | @pViewports@ is a pointer to an array of -- 'Vulkan.Core10.Pipeline.Viewport' structures specifying viewport -- parameters. ("viewports" ::: Vector Viewport) -> io () cmdSetViewport :: CommandBuffer -> ("firstViewport" ::: Word32) -> ("viewports" ::: Vector Viewport) -> io () cmdSetViewport commandBuffer :: CommandBuffer commandBuffer firstViewport :: "firstViewport" ::: Word32 firstViewport viewports :: "viewports" ::: Vector Viewport viewports = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> (ContT () IO () -> IO ()) -> ContT () IO () -> io () forall b c a. (b -> c) -> (a -> b) -> a -> c . ContT () IO () -> IO () forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdSetViewportPtr :: FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) vkCmdSetViewportPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) pVkCmdSetViewport (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) vkCmdSetViewportPtr FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdSetViewport is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdSetViewport' :: Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO () vkCmdSetViewport' = FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) -> Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO () mkVkCmdSetViewport FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) vkCmdSetViewportPtr "pViewports" ::: Ptr Viewport pPViewports <- ((("pViewports" ::: Ptr Viewport) -> IO ()) -> IO ()) -> ContT () IO ("pViewports" ::: Ptr Viewport) forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((("pViewports" ::: Ptr Viewport) -> IO ()) -> IO ()) -> ContT () IO ("pViewports" ::: Ptr Viewport)) -> ((("pViewports" ::: Ptr Viewport) -> IO ()) -> IO ()) -> ContT () IO ("pViewports" ::: Ptr Viewport) forall a b. (a -> b) -> a -> b $ Int -> Int -> (("pViewports" ::: Ptr Viewport) -> IO ()) -> IO () forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned @Viewport ((("viewports" ::: Vector Viewport) -> Int forall a. Vector a -> Int Data.Vector.length ("viewports" ::: Vector Viewport viewports)) Int -> Int -> Int forall a. Num a => a -> a -> a * 24) 4 (Int -> Viewport -> ContT () IO ()) -> ("viewports" ::: Vector Viewport) -> ContT () IO () forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\i :: Int i e :: Viewport e -> ((() -> IO ()) -> IO ()) -> ContT () IO () forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((() -> IO ()) -> IO ()) -> ContT () IO ()) -> ((() -> IO ()) -> IO ()) -> ContT () IO () forall a b. (a -> b) -> a -> b $ ("pViewports" ::: Ptr Viewport) -> Viewport -> IO () -> IO () forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct ("pViewports" ::: Ptr Viewport pPViewports ("pViewports" ::: Ptr Viewport) -> Int -> "pViewports" ::: Ptr Viewport forall a b. Ptr a -> Int -> Ptr b `plusPtr` (24 Int -> Int -> Int forall a. Num a => a -> a -> a * (Int i)) :: Ptr Viewport) (Viewport e) (IO () -> IO ()) -> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO () forall b c a. (b -> c) -> (a -> b) -> a -> c . ((() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ ())) ("viewports" ::: Vector Viewport viewports) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO () vkCmdSetViewport' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("firstViewport" ::: Word32 firstViewport) ((Int -> "firstViewport" ::: Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral (("viewports" ::: Vector Viewport) -> Int forall a. Vector a -> Int Data.Vector.length (("viewports" ::: Vector Viewport) -> Int) -> ("viewports" ::: Vector Viewport) -> Int forall a b. (a -> b) -> a -> b $ ("viewports" ::: Vector Viewport viewports)) :: Word32)) ("pViewports" ::: Ptr Viewport pPViewports) () -> ContT () IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> ContT () IO ()) -> () -> ContT () IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetScissor :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Rect2D -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Rect2D -> IO () -- | vkCmdSetScissor - Set the dynamic scissor rectangles on a command buffer -- -- = Description -- -- The scissor rectangles taken from element i of @pScissors@ replace the -- current state for the scissor index @firstScissor@ + i, for i in [0, -- @scissorCount@). -- -- This command sets the state for a given draw when the graphics pipeline -- is created with 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- -- == Valid Usage -- -- - @firstScissor@ /must/ be less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@ -- -- - The sum of @firstScissor@ and @scissorCount@ /must/ be between @1@ -- and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@, -- inclusive -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports> -- feature is not enabled, @firstScissor@ /must/ be @0@ -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports> -- feature is not enabled, @scissorCount@ /must/ be @1@ -- -- - The @x@ and @y@ members of @offset@ member of any element of -- @pScissors@ /must/ be greater than or equal to @0@ -- -- - Evaluation of (@offset.x@ + @extent.width@) /must/ not cause a -- signed integer addition overflow for any element of @pScissors@ -- -- - Evaluation of (@offset.y@ + @extent.height@) /must/ not cause a -- signed integer addition overflow for any element of @pScissors@ -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @pScissors@ /must/ be a valid pointer to an array of @scissorCount@ -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - @scissorCount@ /must/ be greater than @0@ -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.FundamentalTypes.Rect2D' cmdSetScissor :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @firstScissor@ is the index of the first scissor whose state is updated -- by the command. ("firstScissor" ::: Word32) -> -- | @pScissors@ is a pointer to an array of -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures defining scissor -- rectangles. ("scissors" ::: Vector Rect2D) -> io () cmdSetScissor :: CommandBuffer -> ("firstViewport" ::: Word32) -> ("scissors" ::: Vector Rect2D) -> io () cmdSetScissor commandBuffer :: CommandBuffer commandBuffer firstScissor :: "firstViewport" ::: Word32 firstScissor scissors :: "scissors" ::: Vector Rect2D scissors = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> (ContT () IO () -> IO ()) -> ContT () IO () -> io () forall b c a. (b -> c) -> (a -> b) -> a -> c . ContT () IO () -> IO () forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdSetScissorPtr :: FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) vkCmdSetScissorPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) pVkCmdSetScissor (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) vkCmdSetScissorPtr FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdSetScissor is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdSetScissor' :: Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO () vkCmdSetScissor' = FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) -> Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO () mkVkCmdSetScissor FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) vkCmdSetScissorPtr "pScissors" ::: Ptr Rect2D pPScissors <- ((("pScissors" ::: Ptr Rect2D) -> IO ()) -> IO ()) -> ContT () IO ("pScissors" ::: Ptr Rect2D) forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((("pScissors" ::: Ptr Rect2D) -> IO ()) -> IO ()) -> ContT () IO ("pScissors" ::: Ptr Rect2D)) -> ((("pScissors" ::: Ptr Rect2D) -> IO ()) -> IO ()) -> ContT () IO ("pScissors" ::: Ptr Rect2D) forall a b. (a -> b) -> a -> b $ Int -> Int -> (("pScissors" ::: Ptr Rect2D) -> IO ()) -> IO () forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned @Rect2D ((("scissors" ::: Vector Rect2D) -> Int forall a. Vector a -> Int Data.Vector.length ("scissors" ::: Vector Rect2D scissors)) Int -> Int -> Int forall a. Num a => a -> a -> a * 16) 4 (Int -> Rect2D -> ContT () IO ()) -> ("scissors" ::: Vector Rect2D) -> ContT () IO () forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\i :: Int i e :: Rect2D e -> ((() -> IO ()) -> IO ()) -> ContT () IO () forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((() -> IO ()) -> IO ()) -> ContT () IO ()) -> ((() -> IO ()) -> IO ()) -> ContT () IO () forall a b. (a -> b) -> a -> b $ ("pScissors" ::: Ptr Rect2D) -> Rect2D -> IO () -> IO () forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct ("pScissors" ::: Ptr Rect2D pPScissors ("pScissors" ::: Ptr Rect2D) -> Int -> "pScissors" ::: Ptr Rect2D forall a b. Ptr a -> Int -> Ptr b `plusPtr` (16 Int -> Int -> Int forall a. Num a => a -> a -> a * (Int i)) :: Ptr Rect2D) (Rect2D e) (IO () -> IO ()) -> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO () forall b c a. (b -> c) -> (a -> b) -> a -> c . ((() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ ())) ("scissors" ::: Vector Rect2D scissors) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO () vkCmdSetScissor' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("firstViewport" ::: Word32 firstScissor) ((Int -> "firstViewport" ::: Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral (("scissors" ::: Vector Rect2D) -> Int forall a. Vector a -> Int Data.Vector.length (("scissors" ::: Vector Rect2D) -> Int) -> ("scissors" ::: Vector Rect2D) -> Int forall a b. (a -> b) -> a -> b $ ("scissors" ::: Vector Rect2D scissors)) :: Word32)) ("pScissors" ::: Ptr Rect2D pPScissors) () -> ContT () IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> ContT () IO ()) -> () -> ContT () IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetLineWidth :: FunPtr (Ptr CommandBuffer_T -> CFloat -> IO ()) -> Ptr CommandBuffer_T -> CFloat -> IO () -- | vkCmdSetLineWidth - Set the dynamic line width state -- -- == Valid Usage -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-wideLines wide lines> -- feature is not enabled, @lineWidth@ /must/ be @1.0@ -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer' cmdSetLineWidth :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @lineWidth@ is the width of rasterized line segments. ("lineWidth" ::: Float) -> io () cmdSetLineWidth :: CommandBuffer -> ("lineWidth" ::: Float) -> io () cmdSetLineWidth commandBuffer :: CommandBuffer commandBuffer lineWidth :: "lineWidth" ::: Float lineWidth = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdSetLineWidthPtr :: FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetLineWidthPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()) pVkCmdSetLineWidth (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetLineWidthPtr FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdSetLineWidth is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdSetLineWidth' :: Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO () vkCmdSetLineWidth' = FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()) -> Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO () mkVkCmdSetLineWidth FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetLineWidthPtr Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> IO () vkCmdSetLineWidth' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float lineWidth)) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetDepthBias :: FunPtr (Ptr CommandBuffer_T -> CFloat -> CFloat -> CFloat -> IO ()) -> Ptr CommandBuffer_T -> CFloat -> CFloat -> CFloat -> IO () -- | vkCmdSetDepthBias - Set the depth bias dynamic state -- -- = Description -- -- If @depthBiasEnable@ is 'Vulkan.Core10.FundamentalTypes.FALSE', no depth -- bias is applied and the fragment’s depth values are unchanged. -- -- @depthBiasSlopeFactor@ scales the maximum depth slope of the polygon, -- and @depthBiasConstantFactor@ scales an implementation-dependent -- constant that relates to the usable resolution of the depth buffer. The -- resulting values are summed to produce the depth bias value which is -- then clamped to a minimum or maximum value specified by -- @depthBiasClamp@. @depthBiasSlopeFactor@, @depthBiasConstantFactor@, and -- @depthBiasClamp@ /can/ each be positive, negative, or zero. -- -- The maximum depth slope m of a triangle is -- -- \[m = \sqrt{ \left({{\partial z_f} \over {\partial x_f}}\right)^2 -- + \left({{\partial z_f} \over {\partial y_f}}\right)^2}\] -- -- where (xf, yf, zf) is a point on the triangle. m /may/ be approximated -- as -- -- \[m = \max\left( \left| { {\partial z_f} \over {\partial x_f} } \right|, -- \left| { {\partial z_f} \over {\partial y_f} } \right| -- \right).\] -- -- The minimum resolvable difference r is an implementation-dependent -- parameter that depends on the depth buffer representation. It is the -- smallest difference in framebuffer coordinate z values that is -- guaranteed to remain distinct throughout polygon rasterization and in -- the depth buffer. All pairs of fragments generated by the rasterization -- of two polygons with otherwise identical vertices, but @z@f values that -- differ by r, will have distinct depth values. -- -- For fixed-point depth buffer representations, r is constant throughout -- the range of the entire depth buffer. For floating-point depth buffers, -- there is no single minimum resolvable difference. In this case, the -- minimum resolvable difference for a given polygon is dependent on the -- maximum exponent, e, in the range of z values spanned by the primitive. -- If n is the number of bits in the floating-point mantissa, the minimum -- resolvable difference, r, for the given primitive is defined as -- -- - r = 2e-n -- -- If a triangle is rasterized using the -- 'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_FILL_RECTANGLE_NV' polygon -- mode, then this minimum resolvable difference /may/ not be resolvable -- for samples outside of the triangle, where the depth is extrapolated. -- -- If no depth buffer is present, r is undefined. -- -- The bias value o for a polygon is -- -- \[\begin{aligned} -- o &= \mathrm{dbclamp}( m \times \mathtt{depthBiasSlopeFactor} + r \times \mathtt{depthBiasConstantFactor} ) \\ -- \text{where} &\quad \mathrm{dbclamp}(x) = -- \begin{cases} -- x & \mathtt{depthBiasClamp} = 0 \ \text{or}\ \texttt{NaN} \\ -- \min(x, \mathtt{depthBiasClamp}) & \mathtt{depthBiasClamp} > 0 \\ -- \max(x, \mathtt{depthBiasClamp}) & \mathtt{depthBiasClamp} < 0 \\ -- \end{cases} -- \end{aligned}\] -- -- m is computed as described above. If the depth buffer uses a fixed-point -- representation, m is a function of depth values in the range [0,1], and -- o is applied to depth values in the same range. -- -- For fixed-point depth buffers, fragment depth values are always limited -- to the range [0,1] by clamping after depth bias addition is performed. -- Unless the @VK_EXT_depth_range_unrestricted@ extension is enabled, -- fragment depth values are clamped even when the depth buffer uses a -- floating-point representation. -- -- == Valid Usage -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthBiasClamp depth bias clamping> -- feature is not enabled, @depthBiasClamp@ /must/ be @0.0@ -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer' cmdSetDepthBias :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @depthBiasConstantFactor@ is a scalar factor controlling the constant -- depth value added to each fragment. ("depthBiasConstantFactor" ::: Float) -> -- | @depthBiasClamp@ is the maximum (or minimum) depth bias of a fragment. ("depthBiasClamp" ::: Float) -> -- | @depthBiasSlopeFactor@ is a scalar factor applied to a fragment’s slope -- in depth bias calculations. ("depthBiasSlopeFactor" ::: Float) -> io () cmdSetDepthBias :: CommandBuffer -> ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> io () cmdSetDepthBias commandBuffer :: CommandBuffer commandBuffer depthBiasConstantFactor :: "lineWidth" ::: Float depthBiasConstantFactor depthBiasClamp :: "lineWidth" ::: Float depthBiasClamp depthBiasSlopeFactor :: "lineWidth" ::: Float depthBiasSlopeFactor = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdSetDepthBiasPtr :: FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetDepthBiasPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) pVkCmdSetDepthBias (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetDepthBiasPtr FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdSetDepthBias is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdSetDepthBias' :: Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () vkCmdSetDepthBias' = FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) -> Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () mkVkCmdSetDepthBias FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetDepthBiasPtr Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () vkCmdSetDepthBias' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float depthBiasConstantFactor)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float depthBiasClamp)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float depthBiasSlopeFactor)) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetBlendConstants :: FunPtr (Ptr CommandBuffer_T -> Ptr (FixedArray 4 CFloat) -> IO ()) -> Ptr CommandBuffer_T -> Ptr (FixedArray 4 CFloat) -> IO () -- | vkCmdSetBlendConstants - Set the values of blend constants -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer' cmdSetBlendConstants :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @blendConstants@ is a pointer to an array of four values specifying the -- R, G, B, and A components of the blend constant color used in blending, -- depending on the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blendfactors blend factor>. ("blendConstants" ::: (Float, Float, Float, Float)) -> io () cmdSetBlendConstants :: CommandBuffer -> ("blendConstants" ::: ("lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float)) -> io () cmdSetBlendConstants commandBuffer :: CommandBuffer commandBuffer blendConstants :: "blendConstants" ::: ("lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float) blendConstants = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> (ContT () IO () -> IO ()) -> ContT () IO () -> io () forall b c a. (b -> c) -> (a -> b) -> a -> c . ContT () IO () -> IO () forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdSetBlendConstantsPtr :: FunPtr (Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) vkCmdSetBlendConstantsPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) pVkCmdSetBlendConstants (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) vkCmdSetBlendConstantsPtr FunPtr (Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdSetBlendConstants is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdSetBlendConstants' :: Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO () vkCmdSetBlendConstants' = FunPtr (Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) -> Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO () mkVkCmdSetBlendConstants FunPtr (Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) vkCmdSetBlendConstantsPtr "blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)) pBlendConstants <- ((("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) -> IO ()) -> ContT () IO ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) -> IO ()) -> ContT () IO ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)))) -> ((("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) -> IO ()) -> ContT () IO ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) forall a b. (a -> b) -> a -> b $ Int -> Int -> (("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO ()) -> IO () forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned @(FixedArray 4 CFloat) 16 4 let pBlendConstants' :: Ptr ("lineWidth" ::: CFloat) pBlendConstants' = ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> Ptr ("lineWidth" ::: CFloat) forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a lowerArrayPtr "blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)) pBlendConstants IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ case ("blendConstants" ::: ("lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float, "lineWidth" ::: Float) blendConstants) of (e0 :: "lineWidth" ::: Float e0, e1 :: "lineWidth" ::: Float e1, e2 :: "lineWidth" ::: Float e2, e3 :: "lineWidth" ::: Float e3) -> do Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pBlendConstants' :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e0)) Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pBlendConstants' Ptr ("lineWidth" ::: CFloat) -> Int -> Ptr ("lineWidth" ::: CFloat) forall a b. Ptr a -> Int -> Ptr b `plusPtr` 4 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e1)) Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pBlendConstants' Ptr ("lineWidth" ::: CFloat) -> Int -> Ptr ("lineWidth" ::: CFloat) forall a b. Ptr a -> Int -> Ptr b `plusPtr` 8 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e2)) Ptr ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("lineWidth" ::: CFloat) pBlendConstants' Ptr ("lineWidth" ::: CFloat) -> Int -> Ptr ("lineWidth" ::: CFloat) forall a b. Ptr a -> Int -> Ptr b `plusPtr` 12 :: Ptr CFloat) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float e3)) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Ptr CommandBuffer_T -> ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat))) -> IO () vkCmdSetBlendConstants' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("blendConstants" ::: Ptr (FixedArray 4 ("lineWidth" ::: CFloat)) pBlendConstants) () -> ContT () IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> ContT () IO ()) -> () -> ContT () IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetDepthBounds :: FunPtr (Ptr CommandBuffer_T -> CFloat -> CFloat -> IO ()) -> Ptr CommandBuffer_T -> CFloat -> CFloat -> IO () -- | vkCmdSetDepthBounds - Set the depth bounds test values for a command -- buffer -- -- = Description -- -- This command sets the state for a given draw when the graphics pipeline -- is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- -- == Valid Usage -- -- - Unless the @VK_EXT_depth_range_unrestricted@ extension is enabled -- @minDepthBounds@ /must/ be between @0.0@ and @1.0@, inclusive -- -- - Unless the @VK_EXT_depth_range_unrestricted@ extension is enabled -- @maxDepthBounds@ /must/ be between @0.0@ and @1.0@, inclusive -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer' cmdSetDepthBounds :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @minDepthBounds@ is the minimum depth bound. ("minDepthBounds" ::: Float) -> -- | @maxDepthBounds@ is the maximum depth bound. ("maxDepthBounds" ::: Float) -> io () cmdSetDepthBounds :: CommandBuffer -> ("lineWidth" ::: Float) -> ("lineWidth" ::: Float) -> io () cmdSetDepthBounds commandBuffer :: CommandBuffer commandBuffer minDepthBounds :: "lineWidth" ::: Float minDepthBounds maxDepthBounds :: "lineWidth" ::: Float maxDepthBounds = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdSetDepthBoundsPtr :: FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetDepthBoundsPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) pVkCmdSetDepthBounds (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetDepthBoundsPtr FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdSetDepthBounds is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdSetDepthBounds' :: Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () vkCmdSetDepthBounds' = FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) -> Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () mkVkCmdSetDepthBounds FunPtr (Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO ()) vkCmdSetDepthBoundsPtr Ptr CommandBuffer_T -> ("lineWidth" ::: CFloat) -> ("lineWidth" ::: CFloat) -> IO () vkCmdSetDepthBounds' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float minDepthBounds)) (("lineWidth" ::: Float) -> "lineWidth" ::: CFloat CFloat ("lineWidth" ::: Float maxDepthBounds)) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetStencilCompareMask :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO () -- | vkCmdSetStencilCompareMask - Set the stencil compare mask dynamic state -- -- = Description -- -- This command sets the state for a given draw when the graphics pipeline -- is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_COMPARE_MASK' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @faceMask@ /must/ be a valid combination of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values -- -- - @faceMask@ /must/ not be @0@ -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlags' cmdSetStencilCompareMask :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @faceMask@ is a bitmask of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' specifying -- the set of stencil state for which to update the compare mask. ("faceMask" ::: StencilFaceFlags) -> -- | @compareMask@ is the new value to use as the stencil compare mask. ("compareMask" ::: Word32) -> io () cmdSetStencilCompareMask :: CommandBuffer -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> io () cmdSetStencilCompareMask commandBuffer :: CommandBuffer commandBuffer faceMask :: "faceMask" ::: StencilFaceFlags faceMask compareMask :: "firstViewport" ::: Word32 compareMask = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdSetStencilCompareMaskPtr :: FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilCompareMaskPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) pVkCmdSetStencilCompareMask (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilCompareMaskPtr FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdSetStencilCompareMask is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdSetStencilCompareMask' :: Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () vkCmdSetStencilCompareMask' = FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () mkVkCmdSetStencilCompareMask FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilCompareMaskPtr Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () vkCmdSetStencilCompareMask' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("faceMask" ::: StencilFaceFlags faceMask) ("firstViewport" ::: Word32 compareMask) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetStencilWriteMask :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO () -- | vkCmdSetStencilWriteMask - Set the stencil write mask dynamic state -- -- = Description -- -- This command sets the state for a given draw when the graphics pipeline -- is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_WRITE_MASK' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @faceMask@ /must/ be a valid combination of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values -- -- - @faceMask@ /must/ not be @0@ -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlags' cmdSetStencilWriteMask :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @faceMask@ is a bitmask of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' specifying -- the set of stencil state for which to update the write mask, as -- described above for 'cmdSetStencilCompareMask'. ("faceMask" ::: StencilFaceFlags) -> -- | @writeMask@ is the new value to use as the stencil write mask. ("writeMask" ::: Word32) -> io () cmdSetStencilWriteMask :: CommandBuffer -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> io () cmdSetStencilWriteMask commandBuffer :: CommandBuffer commandBuffer faceMask :: "faceMask" ::: StencilFaceFlags faceMask writeMask :: "firstViewport" ::: Word32 writeMask = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdSetStencilWriteMaskPtr :: FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilWriteMaskPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) pVkCmdSetStencilWriteMask (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilWriteMaskPtr FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdSetStencilWriteMask is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdSetStencilWriteMask' :: Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () vkCmdSetStencilWriteMask' = FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () mkVkCmdSetStencilWriteMask FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilWriteMaskPtr Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () vkCmdSetStencilWriteMask' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("faceMask" ::: StencilFaceFlags faceMask) ("firstViewport" ::: Word32 writeMask) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetStencilReference :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> Word32 -> IO () -- | vkCmdSetStencilReference - Set the stencil reference dynamic state -- -- = Description -- -- This command sets the state for a given draw when the graphics pipeline -- is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_REFERENCE' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @faceMask@ /must/ be a valid combination of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values -- -- - @faceMask@ /must/ not be @0@ -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlags' cmdSetStencilReference :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @faceMask@ is a bitmask of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' specifying -- the set of stencil state for which to update the reference value, as -- described above for 'cmdSetStencilCompareMask'. ("faceMask" ::: StencilFaceFlags) -> -- | @reference@ is the new value to use as the stencil reference value. ("reference" ::: Word32) -> io () cmdSetStencilReference :: CommandBuffer -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> io () cmdSetStencilReference commandBuffer :: CommandBuffer commandBuffer faceMask :: "faceMask" ::: StencilFaceFlags faceMask reference :: "firstViewport" ::: Word32 reference = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdSetStencilReferencePtr :: FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilReferencePtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) pVkCmdSetStencilReference (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilReferencePtr FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdSetStencilReference is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdSetStencilReference' :: Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () vkCmdSetStencilReference' = FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () mkVkCmdSetStencilReference FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdSetStencilReferencePtr Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("firstViewport" ::: Word32) -> IO () vkCmdSetStencilReference' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("faceMask" ::: StencilFaceFlags faceMask) ("firstViewport" ::: Word32 reference) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdBindDescriptorSets :: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr DescriptorSet -> Word32 -> Ptr Word32 -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr DescriptorSet -> Word32 -> Ptr Word32 -> IO () -- | vkCmdBindDescriptorSets - Binds descriptor sets to a command buffer -- -- = Description -- -- 'cmdBindDescriptorSets' causes the sets numbered [@firstSet@.. -- @firstSet@+@descriptorSetCount@-1] to use the bindings stored in -- @pDescriptorSets@[0..descriptorSetCount-1] for subsequent -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipeline-bindpoint-commands bound pipeline commands> -- set by @pipelineBindPoint@. Any bindings that were previously applied -- via these sets are no longer valid. -- -- Once bound, a descriptor set affects rendering of subsequent commands -- that interact with the given pipeline type in the command buffer until -- either a different set is bound to the same set number, or the set is -- disturbed as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility Pipeline Layout Compatibility>. -- -- A compatible descriptor set /must/ be bound for all set numbers that any -- shaders in a pipeline access, at the time that a draw or dispatch -- command is recorded to execute using that pipeline. However, if none of -- the shaders in a pipeline statically use any bindings with a particular -- set number, then no descriptor set need be bound for that set number, -- even if the pipeline layout includes a non-trivial descriptor set layout -- for that set number. -- -- If any of the sets being bound include dynamic uniform or storage -- buffers, then @pDynamicOffsets@ includes one element for each array -- element in each dynamic descriptor type binding in each set. Values are -- taken from @pDynamicOffsets@ in an order such that all entries for set N -- come before set N+1; within a set, entries are ordered by the binding -- numbers in the descriptor set layouts; and within a binding array, -- elements are in order. @dynamicOffsetCount@ /must/ equal the total -- number of dynamic descriptors in the sets being bound. -- -- The effective offset used for dynamic uniform and storage buffer -- bindings is the sum of the relative offset taken from @pDynamicOffsets@, -- and the base address of the buffer plus base offset in the descriptor -- set. The range of the dynamic uniform and storage buffer bindings is the -- buffer range as specified in the descriptor set. -- -- Each of the @pDescriptorSets@ /must/ be compatible with the pipeline -- layout specified by @layout@. The layout used to program the bindings -- /must/ also be compatible with the pipeline used in subsequent -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipeline-bindpoint-commands bound pipeline commands> -- with that pipeline type, as defined in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility Pipeline Layout Compatibility> -- section. -- -- The descriptor set contents bound by a call to 'cmdBindDescriptorSets' -- /may/ be consumed at the following times: -- -- - For descriptor bindings created with the -- 'Vulkan.Core12.Enums.DescriptorBindingFlagBits.DESCRIPTOR_BINDING_UPDATE_AFTER_BIND_BIT' -- bit set, the contents /may/ be consumed when the command buffer is -- submitted to a queue, or during shader execution of the resulting -- draws and dispatches, or any time in between. Otherwise, -- -- - during host execution of the command, or during shader execution of -- the resulting draws and dispatches, or any time in between. -- -- Thus, the contents of a descriptor set binding /must/ not be altered -- (overwritten by an update command, or freed) between the first point in -- time that it /may/ be consumed, and when the command completes executing -- on the queue. -- -- The contents of @pDynamicOffsets@ are consumed immediately during -- execution of 'cmdBindDescriptorSets'. Once all pending uses have -- completed, it is legal to update and reuse a descriptor set. -- -- == Valid Usage -- -- - Each element of @pDescriptorSets@ /must/ have been allocated with a -- 'Vulkan.Core10.Handles.DescriptorSetLayout' that matches (is the -- same as, or identically defined as) the -- 'Vulkan.Core10.Handles.DescriptorSetLayout' at set /n/ in @layout@, -- where /n/ is the sum of @firstSet@ and the index into -- @pDescriptorSets@ -- -- - @dynamicOffsetCount@ /must/ be equal to the total number of dynamic -- descriptors in @pDescriptorSets@ -- -- - The sum of @firstSet@ and @descriptorSetCount@ /must/ be less than -- or equal to -- 'Vulkan.Core10.PipelineLayout.PipelineLayoutCreateInfo'::@setLayoutCount@ -- provided when @layout@ was created -- -- - @pipelineBindPoint@ /must/ be supported by the @commandBuffer@’s -- parent 'Vulkan.Core10.Handles.CommandPool'’s queue family -- -- - Each element of @pDynamicOffsets@ which corresponds to a descriptor -- binding with type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_UNIFORM_BUFFER_DYNAMIC' -- /must/ be a multiple of -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@minUniformBufferOffsetAlignment@ -- -- - Each element of @pDynamicOffsets@ which corresponds to a descriptor -- binding with type -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_BUFFER_DYNAMIC' -- /must/ be a multiple of -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@minStorageBufferOffsetAlignment@ -- -- - For each dynamic uniform or storage buffer binding in -- @pDescriptorSets@, the sum of the effective offset, as defined -- above, and the range of the binding /must/ be less than or equal to -- the size of the buffer -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @pipelineBindPoint@ /must/ be a valid -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value -- -- - @layout@ /must/ be a valid 'Vulkan.Core10.Handles.PipelineLayout' -- handle -- -- - @pDescriptorSets@ /must/ be a valid pointer to an array of -- @descriptorSetCount@ valid 'Vulkan.Core10.Handles.DescriptorSet' -- handles -- -- - If @dynamicOffsetCount@ is not @0@, @pDynamicOffsets@ /must/ be a -- valid pointer to an array of @dynamicOffsetCount@ @uint32_t@ values -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, or compute operations -- -- - @descriptorSetCount@ /must/ be greater than @0@ -- -- - Each of @commandBuffer@, @layout@, and the elements of -- @pDescriptorSets@ /must/ have been created, allocated, or retrieved -- from the same 'Vulkan.Core10.Handles.Device' -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Handles.DescriptorSet', -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint', -- 'Vulkan.Core10.Handles.PipelineLayout' cmdBindDescriptorSets :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer that the descriptor sets will be -- bound to. CommandBuffer -> -- | @pipelineBindPoint@ is a -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' indicating the -- type of the pipeline that will use the descriptors. There is a separate -- set of bind points for each pipeline type, so binding one does not -- disturb the others. PipelineBindPoint -> -- | @layout@ is a 'Vulkan.Core10.Handles.PipelineLayout' object used to -- program the bindings. PipelineLayout -> -- | @firstSet@ is the set number of the first descriptor set to be bound. ("firstSet" ::: Word32) -> -- | @pDescriptorSets@ is a pointer to an array of handles to -- 'Vulkan.Core10.Handles.DescriptorSet' objects describing the descriptor -- sets to write to. ("descriptorSets" ::: Vector DescriptorSet) -> -- | @pDynamicOffsets@ is a pointer to an array of @uint32_t@ values -- specifying dynamic offsets. ("dynamicOffsets" ::: Vector Word32) -> io () cmdBindDescriptorSets :: CommandBuffer -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("descriptorSets" ::: Vector DescriptorSet) -> ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> io () cmdBindDescriptorSets commandBuffer :: CommandBuffer commandBuffer pipelineBindPoint :: PipelineBindPoint pipelineBindPoint layout :: PipelineLayout layout firstSet :: "firstViewport" ::: Word32 firstSet descriptorSets :: "descriptorSets" ::: Vector DescriptorSet descriptorSets dynamicOffsets :: "dynamicOffsets" ::: Vector ("firstViewport" ::: Word32) dynamicOffsets = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> (ContT () IO () -> IO ()) -> ContT () IO () -> io () forall b c a. (b -> c) -> (a -> b) -> a -> c . ContT () IO () -> IO () forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdBindDescriptorSetsPtr :: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) vkCmdBindDescriptorSetsPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) pVkCmdBindDescriptorSets (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) vkCmdBindDescriptorSetsPtr FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdBindDescriptorSets is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdBindDescriptorSets' :: Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO () vkCmdBindDescriptorSets' = FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO () mkVkCmdBindDescriptorSets FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) vkCmdBindDescriptorSetsPtr "pDescriptorSets" ::: Ptr DescriptorSet pPDescriptorSets <- ((("pDescriptorSets" ::: Ptr DescriptorSet) -> IO ()) -> IO ()) -> ContT () IO ("pDescriptorSets" ::: Ptr DescriptorSet) forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((("pDescriptorSets" ::: Ptr DescriptorSet) -> IO ()) -> IO ()) -> ContT () IO ("pDescriptorSets" ::: Ptr DescriptorSet)) -> ((("pDescriptorSets" ::: Ptr DescriptorSet) -> IO ()) -> IO ()) -> ContT () IO ("pDescriptorSets" ::: Ptr DescriptorSet) forall a b. (a -> b) -> a -> b $ Int -> Int -> (("pDescriptorSets" ::: Ptr DescriptorSet) -> IO ()) -> IO () forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned @DescriptorSet ((("descriptorSets" ::: Vector DescriptorSet) -> Int forall a. Vector a -> Int Data.Vector.length ("descriptorSets" ::: Vector DescriptorSet descriptorSets)) Int -> Int -> Int forall a. Num a => a -> a -> a * 8) 8 IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ (Int -> DescriptorSet -> IO ()) -> ("descriptorSets" ::: Vector DescriptorSet) -> IO () forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\i :: Int i e :: DescriptorSet e -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> DescriptorSet -> IO () forall a. Storable a => Ptr a -> a -> IO () poke ("pDescriptorSets" ::: Ptr DescriptorSet pPDescriptorSets ("pDescriptorSets" ::: Ptr DescriptorSet) -> Int -> "pDescriptorSets" ::: Ptr DescriptorSet forall a b. Ptr a -> Int -> Ptr b `plusPtr` (8 Int -> Int -> Int forall a. Num a => a -> a -> a * (Int i)) :: Ptr DescriptorSet) (DescriptorSet e)) ("descriptorSets" ::: Vector DescriptorSet descriptorSets) "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pPDynamicOffsets <- ((("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) -> IO ()) -> ContT () IO ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) -> IO ()) -> ContT () IO ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32))) -> ((("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) -> IO ()) -> ContT () IO ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) forall a b. (a -> b) -> a -> b $ Int -> Int -> (("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO ()) -> IO () forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned @Word32 ((("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> Int forall a. Vector a -> Int Data.Vector.length ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32) dynamicOffsets)) Int -> Int -> Int forall a. Num a => a -> a -> a * 4) 4 IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ (Int -> ("firstViewport" ::: Word32) -> IO ()) -> ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> IO () forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\i :: Int i e :: "firstViewport" ::: Word32 e -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> ("firstViewport" ::: Word32) -> IO () forall a. Storable a => Ptr a -> a -> IO () poke ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pPDynamicOffsets ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> Int -> "pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) forall a b. Ptr a -> Int -> Ptr b `plusPtr` (4 Int -> Int -> Int forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32) ("firstViewport" ::: Word32 e)) ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32) dynamicOffsets) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pDescriptorSets" ::: Ptr DescriptorSet) -> ("firstViewport" ::: Word32) -> ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32)) -> IO () vkCmdBindDescriptorSets' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (PipelineBindPoint pipelineBindPoint) (PipelineLayout layout) ("firstViewport" ::: Word32 firstSet) ((Int -> "firstViewport" ::: Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral (("descriptorSets" ::: Vector DescriptorSet) -> Int forall a. Vector a -> Int Data.Vector.length (("descriptorSets" ::: Vector DescriptorSet) -> Int) -> ("descriptorSets" ::: Vector DescriptorSet) -> Int forall a b. (a -> b) -> a -> b $ ("descriptorSets" ::: Vector DescriptorSet descriptorSets)) :: Word32)) ("pDescriptorSets" ::: Ptr DescriptorSet pPDescriptorSets) ((Int -> "firstViewport" ::: Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral (("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> Int forall a. Vector a -> Int Data.Vector.length (("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> Int) -> ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32)) -> Int forall a b. (a -> b) -> a -> b $ ("dynamicOffsets" ::: Vector ("firstViewport" ::: Word32) dynamicOffsets)) :: Word32)) ("pDynamicOffsets" ::: Ptr ("firstViewport" ::: Word32) pPDynamicOffsets) () -> ContT () IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> ContT () IO ()) -> () -> ContT () IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdBindIndexBuffer :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IndexType -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IndexType -> IO () -- | vkCmdBindIndexBuffer - Bind an index buffer to a command buffer -- -- == Valid Usage -- -- - @offset@ /must/ be less than the size of @buffer@ -- -- - The sum of @offset@ and the address of the range of -- 'Vulkan.Core10.Handles.DeviceMemory' object that is backing -- @buffer@, /must/ be a multiple of the type indicated by @indexType@ -- -- - @buffer@ /must/ have been created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDEX_BUFFER_BIT' -- flag -- -- - If @buffer@ is non-sparse then it /must/ be bound completely and -- contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - @indexType@ /must/ not be -- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_NONE_KHR' -- -- - If @indexType@ is -- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT8_EXT', the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-indexTypeUint8 indexTypeUint8> -- feature /must/ be enabled -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - @indexType@ /must/ be a valid -- 'Vulkan.Core10.Enums.IndexType.IndexType' value -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - Both of @buffer@, and @commandBuffer@ /must/ have been created, -- allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device' -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.FundamentalTypes.DeviceSize', -- 'Vulkan.Core10.Enums.IndexType.IndexType' cmdBindIndexBuffer :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command is -- recorded. CommandBuffer -> -- | @buffer@ is the buffer being bound. Buffer -> -- | @offset@ is the starting offset in bytes within @buffer@ used in index -- buffer address calculations. ("offset" ::: DeviceSize) -> -- | @indexType@ is a 'Vulkan.Core10.Enums.IndexType.IndexType' value -- specifying whether indices are treated as 16 bits or 32 bits. IndexType -> io () cmdBindIndexBuffer :: CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> io () cmdBindIndexBuffer commandBuffer :: CommandBuffer commandBuffer buffer :: Buffer buffer offset :: "offset" ::: DeviceSize offset indexType :: IndexType indexType = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdBindIndexBufferPtr :: FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()) vkCmdBindIndexBufferPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()) pVkCmdBindIndexBuffer (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()) vkCmdBindIndexBufferPtr FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdBindIndexBuffer is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdBindIndexBuffer' :: Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO () vkCmdBindIndexBuffer' = FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO () mkVkCmdBindIndexBuffer FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO ()) vkCmdBindIndexBufferPtr Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IndexType -> IO () vkCmdBindIndexBuffer' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Buffer buffer) ("offset" ::: DeviceSize offset) (IndexType indexType) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdBindVertexBuffers :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Buffer -> Ptr DeviceSize -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Buffer -> Ptr DeviceSize -> IO () -- | vkCmdBindVertexBuffers - Bind vertex buffers to a command buffer -- -- = Description -- -- The values taken from elements i of @pBuffers@ and @pOffsets@ replace -- the current state for the vertex input binding @firstBinding@ + i, for i -- in [0, @bindingCount@). The vertex input binding is updated to start at -- the offset indicated by @pOffsets@[i] from the start of the buffer -- @pBuffers@[i]. All vertex input attributes that use each of these -- bindings will use these updated addresses in their address calculations -- for subsequent draw commands. If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is enabled, elements of @pBuffers@ /can/ be -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and /can/ be used by the -- vertex shader. If a vertex input attribute is bound to a vertex input -- binding that is 'Vulkan.Core10.APIConstants.NULL_HANDLE', the values -- taken from memory are considered to be zero, and missing G, B, or A -- components are -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input-extraction filled with (0,0,1)>. -- -- == Valid Usage -- -- - @firstBinding@ /must/ be less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@ -- -- - The sum of @firstBinding@ and @bindingCount@ /must/ be less than or -- equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@ -- -- - All elements of @pOffsets@ /must/ be less than the size of the -- corresponding element in @pBuffers@ -- -- - All elements of @pBuffers@ /must/ have been created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_VERTEX_BUFFER_BIT' -- flag -- -- - Each element of @pBuffers@ that is non-sparse /must/ be bound -- completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is not enabled, all elements of @pBuffers@ /must/ not be -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - If an element of @pBuffers@ is -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the corresponding -- element of @pOffsets@ /must/ be zero -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @pBuffers@ /must/ be a valid pointer to an array of @bindingCount@ -- valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- 'Vulkan.Core10.Handles.Buffer' handles -- -- - @pOffsets@ /must/ be a valid pointer to an array of @bindingCount@ -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' values -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - @bindingCount@ /must/ be greater than @0@ -- -- - Both of @commandBuffer@, and the elements of @pBuffers@ that are -- valid handles of non-ignored parameters /must/ have been created, -- allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device' -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Both | Graphics | | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' cmdBindVertexBuffers :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command is -- recorded. CommandBuffer -> -- | @firstBinding@ is the index of the first vertex input binding whose -- state is updated by the command. ("firstBinding" ::: Word32) -> -- | @pBuffers@ is a pointer to an array of buffer handles. ("buffers" ::: Vector Buffer) -> -- | @pOffsets@ is a pointer to an array of buffer offsets. ("offsets" ::: Vector DeviceSize) -> io () cmdBindVertexBuffers :: CommandBuffer -> ("firstViewport" ::: Word32) -> ("buffers" ::: Vector Buffer) -> ("offsets" ::: Vector ("offset" ::: DeviceSize)) -> io () cmdBindVertexBuffers commandBuffer :: CommandBuffer commandBuffer firstBinding :: "firstViewport" ::: Word32 firstBinding buffers :: "buffers" ::: Vector Buffer buffers offsets :: "offsets" ::: Vector ("offset" ::: DeviceSize) offsets = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> (ContT () IO () -> IO ()) -> ContT () IO () -> io () forall b c a. (b -> c) -> (a -> b) -> a -> c . ContT () IO () -> IO () forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdBindVertexBuffersPtr :: FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) vkCmdBindVertexBuffersPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) pVkCmdBindVertexBuffers (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) vkCmdBindVertexBuffersPtr FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdBindVertexBuffers is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdBindVertexBuffers' :: Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO () vkCmdBindVertexBuffers' = FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) -> Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO () mkVkCmdBindVertexBuffers FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) vkCmdBindVertexBuffersPtr let pBuffersLength :: Int pBuffersLength = ("buffers" ::: Vector Buffer) -> Int forall a. Vector a -> Int Data.Vector.length (("buffers" ::: Vector Buffer) -> Int) -> ("buffers" ::: Vector Buffer) -> Int forall a b. (a -> b) -> a -> b $ ("buffers" ::: Vector Buffer buffers) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless ((("offsets" ::: Vector ("offset" ::: DeviceSize)) -> Int forall a. Vector a -> Int Data.Vector.length (("offsets" ::: Vector ("offset" ::: DeviceSize)) -> Int) -> ("offsets" ::: Vector ("offset" ::: DeviceSize)) -> Int forall a b. (a -> b) -> a -> b $ ("offsets" ::: Vector ("offset" ::: DeviceSize) offsets)) Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == Int pBuffersLength) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "pOffsets and pBuffers must have the same length" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing "pBuffers" ::: Ptr Buffer pPBuffers <- ((("pBuffers" ::: Ptr Buffer) -> IO ()) -> IO ()) -> ContT () IO ("pBuffers" ::: Ptr Buffer) forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((("pBuffers" ::: Ptr Buffer) -> IO ()) -> IO ()) -> ContT () IO ("pBuffers" ::: Ptr Buffer)) -> ((("pBuffers" ::: Ptr Buffer) -> IO ()) -> IO ()) -> ContT () IO ("pBuffers" ::: Ptr Buffer) forall a b. (a -> b) -> a -> b $ Int -> Int -> (("pBuffers" ::: Ptr Buffer) -> IO ()) -> IO () forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned @Buffer ((("buffers" ::: Vector Buffer) -> Int forall a. Vector a -> Int Data.Vector.length ("buffers" ::: Vector Buffer buffers)) Int -> Int -> Int forall a. Num a => a -> a -> a * 8) 8 IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ (Int -> Buffer -> IO ()) -> ("buffers" ::: Vector Buffer) -> IO () forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\i :: Int i e :: Buffer e -> ("pBuffers" ::: Ptr Buffer) -> Buffer -> IO () forall a. Storable a => Ptr a -> a -> IO () poke ("pBuffers" ::: Ptr Buffer pPBuffers ("pBuffers" ::: Ptr Buffer) -> Int -> "pBuffers" ::: Ptr Buffer forall a b. Ptr a -> Int -> Ptr b `plusPtr` (8 Int -> Int -> Int forall a. Num a => a -> a -> a * (Int i)) :: Ptr Buffer) (Buffer e)) ("buffers" ::: Vector Buffer buffers) "pOffsets" ::: Ptr ("offset" ::: DeviceSize) pPOffsets <- ((("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) -> IO ()) -> ContT () IO ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) -> IO ()) -> ContT () IO ("pOffsets" ::: Ptr ("offset" ::: DeviceSize))) -> ((("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) -> IO ()) -> ContT () IO ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) forall a b. (a -> b) -> a -> b $ Int -> Int -> (("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) -> IO () forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned @DeviceSize ((("offsets" ::: Vector ("offset" ::: DeviceSize)) -> Int forall a. Vector a -> Int Data.Vector.length ("offsets" ::: Vector ("offset" ::: DeviceSize) offsets)) Int -> Int -> Int forall a. Num a => a -> a -> a * 8) 8 IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ (Int -> ("offset" ::: DeviceSize) -> IO ()) -> ("offsets" ::: Vector ("offset" ::: DeviceSize)) -> IO () forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\i :: Int i e :: "offset" ::: DeviceSize e -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> ("offset" ::: DeviceSize) -> IO () forall a. Storable a => Ptr a -> a -> IO () poke ("pOffsets" ::: Ptr ("offset" ::: DeviceSize) pPOffsets ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> Int -> "pOffsets" ::: Ptr ("offset" ::: DeviceSize) forall a b. Ptr a -> Int -> Ptr b `plusPtr` (8 Int -> Int -> Int forall a. Num a => a -> a -> a * (Int i)) :: Ptr DeviceSize) ("offset" ::: DeviceSize e)) ("offsets" ::: Vector ("offset" ::: DeviceSize) offsets) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr ("offset" ::: DeviceSize)) -> IO () vkCmdBindVertexBuffers' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("firstViewport" ::: Word32 firstBinding) ((Int -> "firstViewport" ::: Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral Int pBuffersLength :: Word32)) ("pBuffers" ::: Ptr Buffer pPBuffers) ("pOffsets" ::: Ptr ("offset" ::: DeviceSize) pPOffsets) () -> ContT () IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> ContT () IO ()) -> () -> ContT () IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDraw :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Word32 -> IO () -- | vkCmdDraw - Draw primitives -- -- = Description -- -- When the command is executed, primitives are assembled using the current -- primitive topology and @vertexCount@ consecutive vertex indices with the -- first @vertexIndex@ value equal to @firstVertex@. The primitives are -- drawn @instanceCount@ times with @instanceIndex@ starting with -- @firstInstance@ and increasing sequentially for each instance. The -- assembled primitives execute the bound graphics pipeline. -- -- == Valid Usage -- -- - If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or -- @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and -- @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is -- used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of -- this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using atomic -- operations as a result of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering, as specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' with a -- reduction mode of either -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN' -- or -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX' -- as a result of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering together with minmax filtering, as -- specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.Image' created with a -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV' -- sampled as a result of this command /must/ only be sampled using a -- 'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of -- 'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE' -- -- - For each set /n/ that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a descriptor set /must/ have been bound to /n/ -- at the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for set -- /n/, with the 'Vulkan.Core10.Handles.PipelineLayout' used to create -- the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - For each push constant that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a push constant value /must/ have been set for -- the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for push -- constants, with the 'Vulkan.Core10.Handles.PipelineLayout' used to -- create the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - Descriptors in each bound descriptor set, specified via -- 'cmdBindDescriptorSets', /must/ be valid if they are statically used -- by the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point used by this command -- -- - A valid pipeline /must/ be bound to the pipeline bind point used by -- this command -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command requires any dynamic state, that -- state /must/ have been set for @commandBuffer@, and done so after -- any previously bound pipeline with the corresponding state not -- specified as dynamic -- -- - There /must/ not have been any calls to dynamic state setting -- commands for any state not specified as dynamic in the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command, since that pipeline was bound -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used to sample from any -- 'Vulkan.Core10.Handles.Image' with a -- 'Vulkan.Core10.Handles.ImageView' of the type -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in -- any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions with -- @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions that -- includes a LOD bias or any offset values, in any shader stage -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a uniform buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a storage buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If @commandBuffer@ is an unprotected command buffer, any resource -- accessed by the 'Vulkan.Core10.Handles.Pipeline' object bound to the -- pipeline bind point used by this command /must/ not be a protected -- resource -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.BufferView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Image' objects -- created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects -- created with the -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - The current render pass /must/ be -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible> -- with the @renderPass@ member of the -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure -- specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound -- to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- -- - The subpass index of the current render pass /must/ be equal to the -- @subpass@ member of the -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure -- specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound -- to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- -- - Every input attachment used by the current subpass /must/ be bound -- to the pipeline via a descriptor set -- -- - Image subresources used as attachments in the current render pass -- /must/ not be accessed in any way other than as an attachment by -- this command -- -- - If the draw is recorded in a render pass instance with multiview -- enabled, the maximum instance index /must/ be less than or equal to -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties'::@maxMultiviewInstanceIndex@ -- -- - If the bound graphics pipeline was created with -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- set to 'Vulkan.Core10.FundamentalTypes.TRUE' and the current subpass -- has a depth\/stencil attachment, then that attachment /must/ have -- been created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT' -- bit set -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@ -- of the pipeline -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @scissorCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@ -- of the pipeline -- -- - If the bound graphics pipeline state was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic states enabled then both -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV' -- dynamic state enabled, then the bound graphics pipeline /must/ have -- been created with -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV' -- dynamic state enabled, then the bound graphics pipeline /must/ have -- been created with -- 'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled and an instance of -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV' -- chained from @VkPipelineVieportCreateInfo@, then the bound graphics -- pipeline /must/ have been created with -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled and an instance of -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV' -- chained from @VkPipelineVieportCreateInfo@, then the bound graphics -- pipeline /must/ have been created with -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'::@exclusiveScissorCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @primitiveTopology@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT' -- /must/ be of the same -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-topology-class topology class> -- as the pipeline -- 'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'::@topology@ -- state -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports> -- limit is not supported, the bound graphics pipeline was created with -- the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, and any of the shader stages of the bound -- graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in, -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ be @1@ -- -- - If @commandBuffer@ is a protected command buffer, any resource -- written to by the 'Vulkan.Core10.Handles.Pipeline' object bound to -- the pipeline bind point used by this command /must/ not be an -- unprotected resource -- -- - If @commandBuffer@ is a protected command buffer, pipeline stages -- other than the framebuffer-space and compute stages in the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point /must/ not write to any resource -- -- - All vertex input bindings accessed via vertex input variables -- declared in the vertex shader entry point’s interface /must/ have -- either valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE' buffers -- bound -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is not enabled, all vertex input bindings accessed via -- vertex input variables declared in the vertex shader entry point’s -- interface /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - For a given vertex buffer binding, any attribute data fetched /must/ -- be entirely contained within the corresponding vertex buffer -- binding, as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input ???> -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - This command /must/ only be called inside of a render pass instance -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Inside | Graphics | Graphics | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer' cmdDraw :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command is -- recorded. CommandBuffer -> -- | @vertexCount@ is the number of vertices to draw. ("vertexCount" ::: Word32) -> -- | @instanceCount@ is the number of instances to draw. ("instanceCount" ::: Word32) -> -- | @firstVertex@ is the index of the first vertex to draw. ("firstVertex" ::: Word32) -> -- | @firstInstance@ is the instance ID of the first instance to draw. ("firstInstance" ::: Word32) -> io () cmdDraw :: CommandBuffer -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> io () cmdDraw commandBuffer :: CommandBuffer commandBuffer vertexCount :: "firstViewport" ::: Word32 vertexCount instanceCount :: "firstViewport" ::: Word32 instanceCount firstVertex :: "firstViewport" ::: Word32 firstVertex firstInstance :: "firstViewport" ::: Word32 firstInstance = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdDrawPtr :: FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) pVkCmdDraw (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawPtr FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdDraw is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdDraw' :: Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDraw' = FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () mkVkCmdDraw FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawPtr Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDraw' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("firstViewport" ::: Word32 vertexCount) ("firstViewport" ::: Word32 instanceCount) ("firstViewport" ::: Word32 firstVertex) ("firstViewport" ::: Word32 firstInstance) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDrawIndexed :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Int32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Int32 -> Word32 -> IO () -- | vkCmdDrawIndexed - Issue an indexed draw into a command buffer -- -- = Description -- -- When the command is executed, primitives are assembled using the current -- primitive topology and @indexCount@ vertices whose indices are retrieved -- from the index buffer. The index buffer is treated as an array of -- tightly packed unsigned integers of size defined by the -- 'cmdBindIndexBuffer'::@indexType@ parameter with which the buffer was -- bound. -- -- The first vertex index is at an offset of @firstIndex@ × @indexSize@ + -- @offset@ within the bound index buffer, where @offset@ is the offset -- specified by 'cmdBindIndexBuffer' and @indexSize@ is the byte size of -- the type specified by @indexType@. Subsequent index values are retrieved -- from consecutive locations in the index buffer. Indices are first -- compared to the primitive restart value, then zero extended to 32 bits -- (if the @indexType@ is -- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT8_EXT' or -- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT16') and have -- @vertexOffset@ added to them, before being supplied as the @vertexIndex@ -- value. -- -- The primitives are drawn @instanceCount@ times with @instanceIndex@ -- starting with @firstInstance@ and increasing sequentially for each -- instance. The assembled primitives execute the bound graphics pipeline. -- -- == Valid Usage -- -- - If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or -- @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and -- @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is -- used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of -- this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using atomic -- operations as a result of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering, as specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' with a -- reduction mode of either -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN' -- or -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX' -- as a result of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering together with minmax filtering, as -- specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.Image' created with a -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV' -- sampled as a result of this command /must/ only be sampled using a -- 'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of -- 'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE' -- -- - For each set /n/ that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a descriptor set /must/ have been bound to /n/ -- at the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for set -- /n/, with the 'Vulkan.Core10.Handles.PipelineLayout' used to create -- the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - For each push constant that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a push constant value /must/ have been set for -- the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for push -- constants, with the 'Vulkan.Core10.Handles.PipelineLayout' used to -- create the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - Descriptors in each bound descriptor set, specified via -- 'cmdBindDescriptorSets', /must/ be valid if they are statically used -- by the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point used by this command -- -- - A valid pipeline /must/ be bound to the pipeline bind point used by -- this command -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command requires any dynamic state, that -- state /must/ have been set for @commandBuffer@, and done so after -- any previously bound pipeline with the corresponding state not -- specified as dynamic -- -- - There /must/ not have been any calls to dynamic state setting -- commands for any state not specified as dynamic in the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command, since that pipeline was bound -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used to sample from any -- 'Vulkan.Core10.Handles.Image' with a -- 'Vulkan.Core10.Handles.ImageView' of the type -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in -- any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions with -- @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions that -- includes a LOD bias or any offset values, in any shader stage -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a uniform buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a storage buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If @commandBuffer@ is an unprotected command buffer, any resource -- accessed by the 'Vulkan.Core10.Handles.Pipeline' object bound to the -- pipeline bind point used by this command /must/ not be a protected -- resource -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.BufferView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Image' objects -- created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects -- created with the -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - The current render pass /must/ be -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible> -- with the @renderPass@ member of the -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure -- specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound -- to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- -- - The subpass index of the current render pass /must/ be equal to the -- @subpass@ member of the -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure -- specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound -- to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- -- - Every input attachment used by the current subpass /must/ be bound -- to the pipeline via a descriptor set -- -- - Image subresources used as attachments in the current render pass -- /must/ not be accessed in any way other than as an attachment by -- this command -- -- - If the draw is recorded in a render pass instance with multiview -- enabled, the maximum instance index /must/ be less than or equal to -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties'::@maxMultiviewInstanceIndex@ -- -- - If the bound graphics pipeline was created with -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- set to 'Vulkan.Core10.FundamentalTypes.TRUE' and the current subpass -- has a depth\/stencil attachment, then that attachment /must/ have -- been created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT' -- bit set -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@ -- of the pipeline -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @scissorCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@ -- of the pipeline -- -- - If the bound graphics pipeline state was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic states enabled then both -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV' -- dynamic state enabled, then the bound graphics pipeline /must/ have -- been created with -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV' -- dynamic state enabled, then the bound graphics pipeline /must/ have -- been created with -- 'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled and an instance of -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV' -- chained from @VkPipelineVieportCreateInfo@, then the bound graphics -- pipeline /must/ have been created with -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled and an instance of -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV' -- chained from @VkPipelineVieportCreateInfo@, then the bound graphics -- pipeline /must/ have been created with -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'::@exclusiveScissorCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @primitiveTopology@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT' -- /must/ be of the same -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-topology-class topology class> -- as the pipeline -- 'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'::@topology@ -- state -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports> -- limit is not supported, the bound graphics pipeline was created with -- the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, and any of the shader stages of the bound -- graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in, -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ be @1@ -- -- - If @commandBuffer@ is a protected command buffer, any resource -- written to by the 'Vulkan.Core10.Handles.Pipeline' object bound to -- the pipeline bind point used by this command /must/ not be an -- unprotected resource -- -- - If @commandBuffer@ is a protected command buffer, pipeline stages -- other than the framebuffer-space and compute stages in the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point /must/ not write to any resource -- -- - All vertex input bindings accessed via vertex input variables -- declared in the vertex shader entry point’s interface /must/ have -- either valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE' buffers -- bound -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is not enabled, all vertex input bindings accessed via -- vertex input variables declared in the vertex shader entry point’s -- interface /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - For a given vertex buffer binding, any attribute data fetched /must/ -- be entirely contained within the corresponding vertex buffer -- binding, as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input ???> -- -- - (@indexSize@ × (@firstIndex@ + @indexCount@) + @offset@) /must/ be -- less than or equal to the size of the bound index buffer, with -- @indexSize@ being based on the type specified by @indexType@, where -- the index buffer, @indexType@, and @offset@ are specified via -- 'cmdBindIndexBuffer' -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - This command /must/ only be called inside of a render pass instance -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Inside | Graphics | Graphics | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer' cmdDrawIndexed :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command is -- recorded. CommandBuffer -> -- | @indexCount@ is the number of vertices to draw. ("indexCount" ::: Word32) -> -- | @instanceCount@ is the number of instances to draw. ("instanceCount" ::: Word32) -> -- | @firstIndex@ is the base index within the index buffer. ("firstIndex" ::: Word32) -> -- | @vertexOffset@ is the value added to the vertex index before indexing -- into the vertex buffer. ("vertexOffset" ::: Int32) -> -- | @firstInstance@ is the instance ID of the first instance to draw. ("firstInstance" ::: Word32) -> io () cmdDrawIndexed :: CommandBuffer -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> io () cmdDrawIndexed commandBuffer :: CommandBuffer commandBuffer indexCount :: "firstViewport" ::: Word32 indexCount instanceCount :: "firstViewport" ::: Word32 instanceCount firstIndex :: "firstViewport" ::: Word32 firstIndex vertexOffset :: "vertexOffset" ::: Int32 vertexOffset firstInstance :: "firstViewport" ::: Word32 firstInstance = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdDrawIndexedPtr :: FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndexedPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO ()) pVkCmdDrawIndexed (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndexedPtr FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdDrawIndexed is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdDrawIndexed' :: Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDrawIndexed' = FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO () mkVkCmdDrawIndexed FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndexedPtr Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("vertexOffset" ::: Int32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDrawIndexed' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("firstViewport" ::: Word32 indexCount) ("firstViewport" ::: Word32 instanceCount) ("firstViewport" ::: Word32 firstIndex) ("vertexOffset" ::: Int32 vertexOffset) ("firstViewport" ::: Word32 firstInstance) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDrawIndirect :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO () -- | vkCmdDrawIndirect - Issue an indirect draw into a command buffer -- -- = Description -- -- 'cmdDrawIndirect' behaves similarly to 'cmdDraw' except that the -- parameters are read by the device from a buffer during execution. -- @drawCount@ draws are executed by the command, with parameters taken -- from @buffer@ starting at @offset@ and increasing by @stride@ bytes for -- each successive draw. The parameters of each draw are encoded in an -- array of 'Vulkan.Core10.OtherTypes.DrawIndirectCommand' structures. If -- @drawCount@ is less than or equal to one, @stride@ is ignored. -- -- == Valid Usage -- -- - If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or -- @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and -- @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is -- used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of -- this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using atomic -- operations as a result of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering, as specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' with a -- reduction mode of either -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN' -- or -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX' -- as a result of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering together with minmax filtering, as -- specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.Image' created with a -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV' -- sampled as a result of this command /must/ only be sampled using a -- 'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of -- 'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE' -- -- - For each set /n/ that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a descriptor set /must/ have been bound to /n/ -- at the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for set -- /n/, with the 'Vulkan.Core10.Handles.PipelineLayout' used to create -- the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - For each push constant that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a push constant value /must/ have been set for -- the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for push -- constants, with the 'Vulkan.Core10.Handles.PipelineLayout' used to -- create the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - Descriptors in each bound descriptor set, specified via -- 'cmdBindDescriptorSets', /must/ be valid if they are statically used -- by the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point used by this command -- -- - A valid pipeline /must/ be bound to the pipeline bind point used by -- this command -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command requires any dynamic state, that -- state /must/ have been set for @commandBuffer@, and done so after -- any previously bound pipeline with the corresponding state not -- specified as dynamic -- -- - There /must/ not have been any calls to dynamic state setting -- commands for any state not specified as dynamic in the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command, since that pipeline was bound -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used to sample from any -- 'Vulkan.Core10.Handles.Image' with a -- 'Vulkan.Core10.Handles.ImageView' of the type -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in -- any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions with -- @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions that -- includes a LOD bias or any offset values, in any shader stage -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a uniform buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a storage buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If @commandBuffer@ is an unprotected command buffer, any resource -- accessed by the 'Vulkan.Core10.Handles.Pipeline' object bound to the -- pipeline bind point used by this command /must/ not be a protected -- resource -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.BufferView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Image' objects -- created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects -- created with the -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - The current render pass /must/ be -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible> -- with the @renderPass@ member of the -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure -- specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound -- to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- -- - The subpass index of the current render pass /must/ be equal to the -- @subpass@ member of the -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure -- specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound -- to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- -- - Every input attachment used by the current subpass /must/ be bound -- to the pipeline via a descriptor set -- -- - Image subresources used as attachments in the current render pass -- /must/ not be accessed in any way other than as an attachment by -- this command -- -- - If the draw is recorded in a render pass instance with multiview -- enabled, the maximum instance index /must/ be less than or equal to -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties'::@maxMultiviewInstanceIndex@ -- -- - If the bound graphics pipeline was created with -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- set to 'Vulkan.Core10.FundamentalTypes.TRUE' and the current subpass -- has a depth\/stencil attachment, then that attachment /must/ have -- been created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT' -- bit set -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@ -- of the pipeline -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @scissorCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@ -- of the pipeline -- -- - If the bound graphics pipeline state was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic states enabled then both -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV' -- dynamic state enabled, then the bound graphics pipeline /must/ have -- been created with -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV' -- dynamic state enabled, then the bound graphics pipeline /must/ have -- been created with -- 'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled and an instance of -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV' -- chained from @VkPipelineVieportCreateInfo@, then the bound graphics -- pipeline /must/ have been created with -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled and an instance of -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV' -- chained from @VkPipelineVieportCreateInfo@, then the bound graphics -- pipeline /must/ have been created with -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'::@exclusiveScissorCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @primitiveTopology@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT' -- /must/ be of the same -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-topology-class topology class> -- as the pipeline -- 'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'::@topology@ -- state -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports> -- limit is not supported, the bound graphics pipeline was created with -- the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, and any of the shader stages of the bound -- graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in, -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ be @1@ -- -- - All vertex input bindings accessed via vertex input variables -- declared in the vertex shader entry point’s interface /must/ have -- either valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE' buffers -- bound -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is not enabled, all vertex input bindings accessed via -- vertex input variables declared in the vertex shader entry point’s -- interface /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - For a given vertex buffer binding, any attribute data fetched /must/ -- be entirely contained within the corresponding vertex buffer -- binding, as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input ???> -- -- - If @buffer@ is non-sparse then it /must/ be bound completely and -- contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - @buffer@ /must/ have been created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT' -- bit set -- -- - @offset@ /must/ be a multiple of @4@ -- -- - @commandBuffer@ /must/ not be a protected command buffer -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiDrawIndirect multi-draw indirect> -- feature is not enabled, @drawCount@ /must/ be @0@ or @1@ -- -- - @drawCount@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDrawIndirectCount@ -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-drawIndirectFirstInstance drawIndirectFirstInstance> -- feature is not enabled, all the @firstInstance@ members of the -- 'Vulkan.Core10.OtherTypes.DrawIndirectCommand' structures accessed -- by this command /must/ be @0@ -- -- - If @drawCount@ is greater than @1@, @stride@ /must/ be a multiple of -- @4@ and /must/ be greater than or equal to -- @sizeof@('Vulkan.Core10.OtherTypes.DrawIndirectCommand') -- -- - If @drawCount@ is equal to @1@, (@offset@ + -- @sizeof@('Vulkan.Core10.OtherTypes.DrawIndirectCommand')) /must/ be -- less than or equal to the size of @buffer@ -- -- - If @drawCount@ is greater than @1@, (@stride@ × (@drawCount@ - 1) + -- @offset@ + @sizeof@('Vulkan.Core10.OtherTypes.DrawIndirectCommand')) -- /must/ be less than or equal to the size of @buffer@ -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - This command /must/ only be called inside of a render pass instance -- -- - Both of @buffer@, and @commandBuffer@ /must/ have been created, -- allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device' -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Inside | Graphics | Graphics | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' cmdDrawIndirect :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command is -- recorded. CommandBuffer -> -- | @buffer@ is the buffer containing draw parameters. Buffer -> -- | @offset@ is the byte offset into @buffer@ where parameters begin. ("offset" ::: DeviceSize) -> -- | @drawCount@ is the number of draws to execute, and /can/ be zero. ("drawCount" ::: Word32) -> -- | @stride@ is the byte stride between successive sets of draw parameters. ("stride" ::: Word32) -> io () cmdDrawIndirect :: CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> io () cmdDrawIndirect commandBuffer :: CommandBuffer commandBuffer buffer :: Buffer buffer offset :: "offset" ::: DeviceSize offset drawCount :: "firstViewport" ::: Word32 drawCount stride :: "firstViewport" ::: Word32 stride = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdDrawIndirectPtr :: FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndirectPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) pVkCmdDrawIndirect (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndirectPtr FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdDrawIndirect is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdDrawIndirect' :: Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDrawIndirect' = FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () mkVkCmdDrawIndirect FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndirectPtr Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDrawIndirect' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Buffer buffer) ("offset" ::: DeviceSize offset) ("firstViewport" ::: Word32 drawCount) ("firstViewport" ::: Word32 stride) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDrawIndexedIndirect :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> Word32 -> Word32 -> IO () -- | vkCmdDrawIndexedIndirect - Perform an indexed indirect draw -- -- = Description -- -- 'cmdDrawIndexedIndirect' behaves similarly to 'cmdDrawIndexed' except -- that the parameters are read by the device from a buffer during -- execution. @drawCount@ draws are executed by the command, with -- parameters taken from @buffer@ starting at @offset@ and increasing by -- @stride@ bytes for each successive draw. The parameters of each draw are -- encoded in an array of -- 'Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand' structures. If -- @drawCount@ is less than or equal to one, @stride@ is ignored. -- -- == Valid Usage -- -- - If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or -- @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and -- @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is -- used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of -- this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using atomic -- operations as a result of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering, as specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' with a -- reduction mode of either -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN' -- or -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX' -- as a result of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering together with minmax filtering, as -- specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.Image' created with a -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV' -- sampled as a result of this command /must/ only be sampled using a -- 'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of -- 'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE' -- -- - For each set /n/ that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a descriptor set /must/ have been bound to /n/ -- at the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for set -- /n/, with the 'Vulkan.Core10.Handles.PipelineLayout' used to create -- the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - For each push constant that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a push constant value /must/ have been set for -- the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for push -- constants, with the 'Vulkan.Core10.Handles.PipelineLayout' used to -- create the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - Descriptors in each bound descriptor set, specified via -- 'cmdBindDescriptorSets', /must/ be valid if they are statically used -- by the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point used by this command -- -- - A valid pipeline /must/ be bound to the pipeline bind point used by -- this command -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command requires any dynamic state, that -- state /must/ have been set for @commandBuffer@, and done so after -- any previously bound pipeline with the corresponding state not -- specified as dynamic -- -- - There /must/ not have been any calls to dynamic state setting -- commands for any state not specified as dynamic in the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command, since that pipeline was bound -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used to sample from any -- 'Vulkan.Core10.Handles.Image' with a -- 'Vulkan.Core10.Handles.ImageView' of the type -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in -- any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions with -- @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions that -- includes a LOD bias or any offset values, in any shader stage -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a uniform buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a storage buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If @commandBuffer@ is an unprotected command buffer, any resource -- accessed by the 'Vulkan.Core10.Handles.Pipeline' object bound to the -- pipeline bind point used by this command /must/ not be a protected -- resource -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.BufferView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Image' objects -- created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects -- created with the -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - The current render pass /must/ be -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility compatible> -- with the @renderPass@ member of the -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure -- specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound -- to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- -- - The subpass index of the current render pass /must/ be equal to the -- @subpass@ member of the -- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo' structure -- specified when creating the 'Vulkan.Core10.Handles.Pipeline' bound -- to -- 'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS' -- -- - Every input attachment used by the current subpass /must/ be bound -- to the pipeline via a descriptor set -- -- - Image subresources used as attachments in the current render pass -- /must/ not be accessed in any way other than as an attachment by -- this command -- -- - If the draw is recorded in a render pass instance with multiview -- enabled, the maximum instance index /must/ be less than or equal to -- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties'::@maxMultiviewInstanceIndex@ -- -- - If the bound graphics pipeline was created with -- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@ -- set to 'Vulkan.Core10.FundamentalTypes.TRUE' and the current subpass -- has a depth\/stencil attachment, then that attachment /must/ have -- been created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT' -- bit set -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@ -- of the pipeline -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @scissorCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ match the -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@ -- of the pipeline -- -- - If the bound graphics pipeline state was created with both the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic states enabled then both -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- and -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ match the @scissorCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV' -- dynamic state enabled, then the bound graphics pipeline /must/ have -- been created with -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, but not the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV' -- dynamic state enabled, then the bound graphics pipeline /must/ have -- been created with -- 'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- and -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV' -- dynamic states enabled then the @viewportCount@ parameter in the -- last call to -- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV' -- /must/ be greater than or equal to the @viewportCount@ parameter in -- the last call to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled and an instance of -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV' -- chained from @VkPipelineVieportCreateInfo@, then the bound graphics -- pipeline /must/ have been created with -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@viewportCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled and an instance of -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV' -- chained from @VkPipelineVieportCreateInfo@, then the bound graphics -- pipeline /must/ have been created with -- 'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'::@exclusiveScissorCount@ -- greater or equal to the @viewportCount@ parameter in the last call -- to -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- -- - If the bound graphics pipeline state was created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @primitiveTopology@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT' -- /must/ be of the same -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing-primitive-topology-class topology class> -- as the pipeline -- 'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'::@topology@ -- state -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports> -- limit is not supported, the bound graphics pipeline was created with -- the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT' -- dynamic state enabled, and any of the shader stages of the bound -- graphics pipeline write to the @PrimitiveShadingRateKHR@ built-in, -- then -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ have been called in the current command buffer prior to this -- draw command, and the @viewportCount@ parameter of -- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT' -- /must/ be @1@ -- -- - All vertex input bindings accessed via vertex input variables -- declared in the vertex shader entry point’s interface /must/ have -- either valid or 'Vulkan.Core10.APIConstants.NULL_HANDLE' buffers -- bound -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is not enabled, all vertex input bindings accessed via -- vertex input variables declared in the vertex shader entry point’s -- interface /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - For a given vertex buffer binding, any attribute data fetched /must/ -- be entirely contained within the corresponding vertex buffer -- binding, as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input ???> -- -- - If @buffer@ is non-sparse then it /must/ be bound completely and -- contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - @buffer@ /must/ have been created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT' -- bit set -- -- - @offset@ /must/ be a multiple of @4@ -- -- - @commandBuffer@ /must/ not be a protected command buffer -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiDrawIndirect multi-draw indirect> -- feature is not enabled, @drawCount@ /must/ be @0@ or @1@ -- -- - @drawCount@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxDrawIndirectCount@ -- -- - If @drawCount@ is greater than @1@, @stride@ /must/ be a multiple of -- @4@ and /must/ be greater than or equal to -- @sizeof@('Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand') -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-drawIndirectFirstInstance drawIndirectFirstInstance> -- feature is not enabled, all the @firstInstance@ members of the -- 'Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand' structures -- accessed by this command /must/ be @0@ -- -- - If @drawCount@ is equal to @1@, (@offset@ + -- @sizeof@('Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand')) -- /must/ be less than or equal to the size of @buffer@ -- -- - If @drawCount@ is greater than @1@, (@stride@ × (@drawCount@ - 1) + -- @offset@ + -- @sizeof@('Vulkan.Core10.OtherTypes.DrawIndexedIndirectCommand')) -- /must/ be less than or equal to the size of @buffer@ -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - This command /must/ only be called inside of a render pass instance -- -- - Both of @buffer@, and @commandBuffer@ /must/ have been created, -- allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device' -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Inside | Graphics | Graphics | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' cmdDrawIndexedIndirect :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command is -- recorded. CommandBuffer -> -- | @buffer@ is the buffer containing draw parameters. Buffer -> -- | @offset@ is the byte offset into @buffer@ where parameters begin. ("offset" ::: DeviceSize) -> -- | @drawCount@ is the number of draws to execute, and /can/ be zero. ("drawCount" ::: Word32) -> -- | @stride@ is the byte stride between successive sets of draw parameters. ("stride" ::: Word32) -> io () cmdDrawIndexedIndirect :: CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> io () cmdDrawIndexedIndirect commandBuffer :: CommandBuffer commandBuffer buffer :: Buffer buffer offset :: "offset" ::: DeviceSize offset drawCount :: "firstViewport" ::: Word32 drawCount stride :: "firstViewport" ::: Word32 stride = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdDrawIndexedIndirectPtr :: FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndexedIndirectPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) pVkCmdDrawIndexedIndirect (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndexedIndirectPtr FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdDrawIndexedIndirect is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdDrawIndexedIndirect' :: Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDrawIndexedIndirect' = FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () mkVkCmdDrawIndexedIndirect FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDrawIndexedIndirectPtr Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDrawIndexedIndirect' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Buffer buffer) ("offset" ::: DeviceSize offset) ("firstViewport" ::: Word32 drawCount) ("firstViewport" ::: Word32 stride) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDispatch :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> IO () -- | vkCmdDispatch - Dispatch compute work items -- -- = Description -- -- When the command is executed, a global workgroup consisting of -- @groupCountX@ × @groupCountY@ × @groupCountZ@ local workgroups is -- assembled. -- -- == Valid Usage -- -- - If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or -- @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and -- @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is -- used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of -- this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using atomic -- operations as a result of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering, as specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' with a -- reduction mode of either -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN' -- or -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX' -- as a result of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering together with minmax filtering, as -- specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.Image' created with a -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV' -- sampled as a result of this command /must/ only be sampled using a -- 'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of -- 'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE' -- -- - For each set /n/ that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a descriptor set /must/ have been bound to /n/ -- at the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for set -- /n/, with the 'Vulkan.Core10.Handles.PipelineLayout' used to create -- the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - For each push constant that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a push constant value /must/ have been set for -- the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for push -- constants, with the 'Vulkan.Core10.Handles.PipelineLayout' used to -- create the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - Descriptors in each bound descriptor set, specified via -- 'cmdBindDescriptorSets', /must/ be valid if they are statically used -- by the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point used by this command -- -- - A valid pipeline /must/ be bound to the pipeline bind point used by -- this command -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command requires any dynamic state, that -- state /must/ have been set for @commandBuffer@, and done so after -- any previously bound pipeline with the corresponding state not -- specified as dynamic -- -- - There /must/ not have been any calls to dynamic state setting -- commands for any state not specified as dynamic in the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command, since that pipeline was bound -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used to sample from any -- 'Vulkan.Core10.Handles.Image' with a -- 'Vulkan.Core10.Handles.ImageView' of the type -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in -- any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions with -- @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions that -- includes a LOD bias or any offset values, in any shader stage -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a uniform buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a storage buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If @commandBuffer@ is an unprotected command buffer, any resource -- accessed by the 'Vulkan.Core10.Handles.Pipeline' object bound to the -- pipeline bind point used by this command /must/ not be a protected -- resource -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.BufferView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Image' objects -- created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects -- created with the -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - If @commandBuffer@ is a protected command buffer, any resource -- written to by the 'Vulkan.Core10.Handles.Pipeline' object bound to -- the pipeline bind point used by this command /must/ not be an -- unprotected resource -- -- - If @commandBuffer@ is a protected command buffer, pipeline stages -- other than the framebuffer-space and compute stages in the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point /must/ not write to any resource -- -- - @groupCountX@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0] -- -- - @groupCountY@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1] -- -- - @groupCountZ@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2] -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support compute operations -- -- - This command /must/ only be called outside of a render pass instance -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Outside | Compute | Compute | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.CommandBuffer' cmdDispatch :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @groupCountX@ is the number of local workgroups to dispatch in the X -- dimension. ("groupCountX" ::: Word32) -> -- | @groupCountY@ is the number of local workgroups to dispatch in the Y -- dimension. ("groupCountY" ::: Word32) -> -- | @groupCountZ@ is the number of local workgroups to dispatch in the Z -- dimension. ("groupCountZ" ::: Word32) -> io () cmdDispatch :: CommandBuffer -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> io () cmdDispatch commandBuffer :: CommandBuffer commandBuffer groupCountX :: "firstViewport" ::: Word32 groupCountX groupCountY :: "firstViewport" ::: Word32 groupCountY groupCountZ :: "firstViewport" ::: Word32 groupCountZ = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdDispatchPtr :: FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDispatchPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) pVkCmdDispatch (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDispatchPtr FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdDispatch is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdDispatch' :: Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDispatch' = FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () mkVkCmdDispatch FunPtr (Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO ()) vkCmdDispatchPtr Ptr CommandBuffer_T -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> ("firstViewport" ::: Word32) -> IO () vkCmdDispatch' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("firstViewport" ::: Word32 groupCountX) ("firstViewport" ::: Word32 groupCountY) ("firstViewport" ::: Word32 groupCountZ) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDispatchIndirect :: FunPtr (Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> DeviceSize -> IO () -- | vkCmdDispatchIndirect - Dispatch compute work items using indirect -- parameters -- -- = Description -- -- 'cmdDispatchIndirect' behaves similarly to 'cmdDispatch' except that the -- parameters are read by the device from a buffer during execution. The -- parameters of the dispatch are encoded in a -- 'Vulkan.Core10.OtherTypes.DispatchIndirectCommand' structure taken from -- @buffer@ starting at @offset@. -- -- == Valid Usage -- -- - If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or -- @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and -- @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is -- used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of -- this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using atomic -- operations as a result of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT' -- -- - If a 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result -- of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering, as specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' with a -- reduction mode of either -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN' -- or -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX' -- as a result of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering together with minmax filtering, as -- specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - Any 'Vulkan.Core10.Handles.Image' created with a -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV' -- sampled as a result of this command /must/ only be sampled using a -- 'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of -- 'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE' -- -- - For each set /n/ that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a descriptor set /must/ have been bound to /n/ -- at the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for set -- /n/, with the 'Vulkan.Core10.Handles.PipelineLayout' used to create -- the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - For each push constant that is statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command, a push constant value /must/ have been set for -- the same pipeline bind point, with a -- 'Vulkan.Core10.Handles.PipelineLayout' that is compatible for push -- constants, with the 'Vulkan.Core10.Handles.PipelineLayout' used to -- create the current 'Vulkan.Core10.Handles.Pipeline', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - Descriptors in each bound descriptor set, specified via -- 'cmdBindDescriptorSets', /must/ be valid if they are statically used -- by the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind -- point used by this command -- -- - A valid pipeline /must/ be bound to the pipeline bind point used by -- this command -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command requires any dynamic state, that -- state /must/ have been set for @commandBuffer@, and done so after -- any previously bound pipeline with the corresponding state not -- specified as dynamic -- -- - There /must/ not have been any calls to dynamic state setting -- commands for any state not specified as dynamic in the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command, since that pipeline was bound -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used to sample from any -- 'Vulkan.Core10.Handles.Image' with a -- 'Vulkan.Core10.Handles.ImageView' of the type -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in -- any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions with -- @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage -- -- - If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline -- bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions that -- includes a LOD bias or any offset values, in any shader stage -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a uniform buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access> -- feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline' -- object bound to the pipeline bind point used by this command -- accesses a storage buffer, it /must/ not access values outside of -- the range of the buffer as specified in the descriptor set bound to -- the same pipeline bind point -- -- - If @commandBuffer@ is an unprotected command buffer, any resource -- accessed by the 'Vulkan.Core10.Handles.Pipeline' object bound to the -- pipeline bind point used by this command /must/ not be a protected -- resource -- -- - If a 'Vulkan.Core10.Handles.ImageView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.BufferView' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width -- is accessed as a result of this command, the @SampledType@ of the -- @OpTypeImage@ operand of that instruction /must/ have a @Width@ of -- 64. -- -- - If a 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a channel width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Image' objects -- created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects -- created with the -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command. -- -- - If @buffer@ is non-sparse then it /must/ be bound completely and -- contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - @buffer@ /must/ have been created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT' -- bit set -- -- - @offset@ /must/ be a multiple of @4@ -- -- - @commandBuffer@ /must/ not be a protected command buffer -- -- - The sum of @offset@ and the size of -- 'Vulkan.Core10.OtherTypes.DispatchIndirectCommand' /must/ be less -- than or equal to the size of @buffer@ -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support compute operations -- -- - This command /must/ only be called outside of a render pass instance -- -- - Both of @buffer@, and @commandBuffer@ /must/ have been created, -- allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device' -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Outside | Compute | Compute | -- | Secondary | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' cmdDispatchIndirect :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @buffer@ is the buffer containing dispatch parameters. Buffer -> -- | @offset@ is the byte offset into @buffer@ where parameters begin. ("offset" ::: DeviceSize) -> io () cmdDispatchIndirect :: CommandBuffer -> Buffer -> ("offset" ::: DeviceSize) -> io () cmdDispatchIndirect commandBuffer :: CommandBuffer commandBuffer buffer :: Buffer buffer offset :: "offset" ::: DeviceSize offset = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdDispatchIndirectPtr :: FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()) vkCmdDispatchIndirectPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()) pVkCmdDispatchIndirect (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()) vkCmdDispatchIndirectPtr FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdDispatchIndirect is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdDispatchIndirect' :: Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO () vkCmdDispatchIndirect' = FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO () mkVkCmdDispatchIndirect FunPtr (Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO ()) vkCmdDispatchIndirectPtr Ptr CommandBuffer_T -> Buffer -> ("offset" ::: DeviceSize) -> IO () vkCmdDispatchIndirect' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Buffer buffer) ("offset" ::: DeviceSize offset) () -> IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdCopyBuffer :: FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> Word32 -> Ptr BufferCopy -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> Buffer -> Word32 -> Ptr BufferCopy -> IO () -- | vkCmdCopyBuffer - Copy data between buffer regions -- -- = Description -- -- Each region in @pRegions@ is copied from the source buffer to the same -- region of the destination buffer. @srcBuffer@ and @dstBuffer@ /can/ be -- the same buffer or alias the same memory, but the resulting values are -- undefined if the copy regions overlap in memory. -- -- == Valid Usage -- -- - If @commandBuffer@ is an unprotected command buffer, then -- @srcBuffer@ /must/ not be a protected buffer -- -- - If @commandBuffer@ is an unprotected command buffer, then -- @dstBuffer@ /must/ not be a protected buffer -- -- - If @commandBuffer@ is a protected command buffer, then @dstBuffer@ -- /must/ not be an unprotected buffer -- -- - The @srcOffset@ member of each element of @pRegions@ /must/ be less -- than the size of @srcBuffer@ -- -- - The @dstOffset@ member of each element of @pRegions@ /must/ be less -- than the size of @dstBuffer@ -- -- - The @size@ member of each element of @pRegions@ /must/ be less than -- or equal to the size of @srcBuffer@ minus @srcOffset@ -- -- - The @size@ member of each element of @pRegions@ /must/ be less than -- or equal to the size of @dstBuffer@ minus @dstOffset@ -- -- - The union of the source regions, and the union of the destination -- regions, specified by the elements of @pRegions@, /must/ not overlap -- in memory -- -- - @srcBuffer@ /must/ have been created with -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_SRC_BIT' -- usage flag -- -- - If @srcBuffer@ is non-sparse then it /must/ be bound completely and -- contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - @dstBuffer@ /must/ have been created with -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - If @dstBuffer@ is non-sparse then it /must/ be bound completely and -- contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- == Valid Usage (Implicit) -- -- - @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - @srcBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - @dstBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle -- -- - @pRegions@ /must/ be a valid pointer to an array of @regionCount@ -- valid 'BufferCopy' structures -- -- - @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support transfer, graphics, or compute -- operations -- -- - This command /must/ only be called outside of a render pass instance -- -- - @regionCount@ /must/ be greater than @0@ -- -- - Each of @commandBuffer@, @dstBuffer@, and @srcBuffer@ /must/ have -- been created, allocated, or retrieved from the same -- 'Vulkan.Core10.Handles.Device' -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> | -- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+ -- | Primary | Outside | Transfer | Transfer | -- | Secondary | | Graphics | | -- | | | Compute | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- 'Vulkan.Core10.Handles.Buffer', 'BufferCopy', -- 'Vulkan.Core10.Handles.CommandBuffer' cmdCopyBuffer :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @srcBuffer@ is the source buffer. ("srcBuffer" ::: Buffer) -> -- | @dstBuffer@ is the destination buffer. ("dstBuffer" ::: Buffer) -> -- | @pRegions@ is a pointer to an array of 'BufferCopy' structures -- specifying the regions to copy. ("regions" ::: Vector BufferCopy) -> io () cmdCopyBuffer :: CommandBuffer -> Buffer -> Buffer -> ("regions" ::: Vector BufferCopy) -> io () cmdCopyBuffer commandBuffer :: CommandBuffer commandBuffer srcBuffer :: Buffer srcBuffer dstBuffer :: Buffer dstBuffer regions :: "regions" ::: Vector BufferCopy regions = IO () -> io () forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO () -> io ()) -> (ContT () IO () -> IO ()) -> ContT () IO () -> io () forall b c a. (b -> c) -> (a -> b) -> a -> c . ContT () IO () -> IO () forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io () forall a b. (a -> b) -> a -> b $ do let vkCmdCopyBufferPtr :: FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()) vkCmdCopyBufferPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()) pVkCmdCopyBuffer (CommandBuffer -> DeviceCmds deviceCmds (CommandBuffer commandBuffer :: CommandBuffer)) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Bool -> IO () -> IO () forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()) vkCmdCopyBufferPtr FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()) -> FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()) -> Bool forall a. Eq a => a -> a -> Bool /= FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()) forall a. FunPtr a nullFunPtr) (IO () -> IO ()) -> IO () -> IO () forall a b. (a -> b) -> a -> b $ IOException -> IO () forall e a. Exception e => e -> IO a throwIO (IOException -> IO ()) -> IOException -> IO () forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError Maybe Handle forall a. Maybe a Nothing IOErrorType InvalidArgument "" "The function pointer for vkCmdCopyBuffer is null" Maybe CInt forall a. Maybe a Nothing Maybe String forall a. Maybe a Nothing let vkCmdCopyBuffer' :: Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO () vkCmdCopyBuffer' = FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()) -> Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO () mkVkCmdCopyBuffer FunPtr (Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()) vkCmdCopyBufferPtr "pRegions" ::: Ptr BufferCopy pPRegions <- ((("pRegions" ::: Ptr BufferCopy) -> IO ()) -> IO ()) -> ContT () IO ("pRegions" ::: Ptr BufferCopy) forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((("pRegions" ::: Ptr BufferCopy) -> IO ()) -> IO ()) -> ContT () IO ("pRegions" ::: Ptr BufferCopy)) -> ((("pRegions" ::: Ptr BufferCopy) -> IO ()) -> IO ()) -> ContT () IO ("pRegions" ::: Ptr BufferCopy) forall a b. (a -> b) -> a -> b $ Int -> Int -> (("pRegions" ::: Ptr BufferCopy) -> IO ()) -> IO () forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b allocaBytesAligned @BufferCopy ((("regions" ::: Vector BufferCopy) -> Int forall a. Vector a -> Int Data.Vector.length ("regions" ::: Vector BufferCopy regions)) Int -> Int -> Int forall a. Num a => a -> a -> a * 24) 8 (Int -> BufferCopy -> ContT () IO ()) -> ("regions" ::: Vector BufferCopy) -> ContT () IO () forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\i :: Int i e :: BufferCopy e -> ((() -> IO ()) -> IO ()) -> ContT () IO () forall k (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT (((() -> IO ()) -> IO ()) -> ContT () IO ()) -> ((() -> IO ()) -> IO ()) -> ContT () IO () forall a b. (a -> b) -> a -> b $ ("pRegions" ::: Ptr BufferCopy) -> BufferCopy -> IO () -> IO () forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct ("pRegions" ::: Ptr BufferCopy pPRegions ("pRegions" ::: Ptr BufferCopy) -> Int -> "pRegions" ::: Ptr BufferCopy forall a b. Ptr a -> Int -> Ptr b `plusPtr` (24 Int -> Int -> Int forall a. Num a => a -> a -> a * (Int i)) :: Ptr BufferCopy) (BufferCopy e) (IO () -> IO ()) -> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO () forall b c a. (b -> c) -> (a -> b) -> a -> c . ((() -> IO ()) -> () -> IO () forall a b. (a -> b) -> a -> b $ ())) ("regions" ::: Vector BufferCopy regions) IO () -> ContT () IO () forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO () forall a b. (a -> b) -> a -> b $ Ptr CommandBuffer_T -> Buffer -> Buffer -> ("firstViewport" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO () vkCmdCopyBuffer' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Buffer srcBuffer) (Buffer dstBuffer) ((Int -> "firstViewport" ::: Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral (("regions" ::: Vector BufferCopy) -> Int forall a. Vector a -> Int Data.Vector.length (("regions" ::: Vector BufferCopy) -> Int) -> ("regions" ::: Vector BufferCopy) -> Int forall a b. (a -> b) -> a -> b $ ("regions" ::: Vector BufferCopy regions)) :: Word32)) ("pRegions" ::: Ptr BufferCopy pPRegions) () -> ContT () IO () forall (f :: * -> *) a. Applicative f => a -> f a pure (() -> ContT () IO ()) -> () -> ContT () IO () forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdCopyImage :: FunPtr (Ptr CommandBuffer_T -> Image -> ImageLayout -> Image -> ImageLayout -> Word32 -> Ptr ImageCopy -> IO ()) -> Ptr CommandBuffer_T -> Image -> ImageLayout -> Image -> ImageLayout -> Word32 -> Ptr ImageCopy -> IO () -- | vkCmdCopyImage - Copy data between images -- -- = Description -- -- Each region in @pRegions@ is copied from the source image to the same -- region of the destination image. @srcImage@ and @dstImage@ /can/ be the -- same image or alias the same memory. -- -- The formats of @srcImage@ and @dstImage@ /must/ be compatible. Formats -- are compatible if they share the same class, as shown in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatibility Compatible Formats> -- table. Depth\/stencil formats /must/ match exactly. -- -- If the format of @srcImage@ or @dstImage@ is a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format>, -- regions of each plane to be copied /must/ be specified separately using -- the @srcSubresource@ and @dstSubresource@ members of the 'ImageCopy' -- structure. In this case, the @aspectMask@ of the @srcSubresource@ or -- @dstSubresource@ that refers to the multi-planar image /must/ be -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT', or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT'. For -- the purposes of 'cmdCopyImage', each plane of a multi-planar image is -- treated as having the format listed in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatible-planes> -- for the plane identified by the @aspectMask@ of the corresponding -- subresource. This applies both to 'Vulkan.Core10.Enums.Format.Format' -- and to coordinates used in the copy, which correspond to texels in the -- /plane/ rather than how these texels map to coordinates in the image as -- a whole. -- -- Note -- -- For example, the -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' plane -- of a 'Vulkan.Core10.Enums.Format.FORMAT_G8_B8R8_2PLANE_420_UNORM' image -- is compatible with an image of format -- 'Vulkan.Core10.Enums.Format.FORMAT_R8G8_UNORM' and (less usefully) with -- the 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' -- plane of an image of format -- 'Vulkan.Core10.Enums.Format.FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16', -- as each texel is 2 bytes in size. -- -- 'cmdCopyImage' allows copying between /size-compatible/ compressed and -- uncompressed internal formats. Formats are size-compatible if the texel -- block size of the uncompressed format is equal to the texel block size -- of the compressed format. Such a copy does not perform on-the-fly -- compression or decompression. When copying from an uncompressed format -- to a compressed format, each texel of uncompressed data of the source -- image is copied as a raw value to the corresponding compressed texel -- block of the destination image. When copying from a compressed format to -- an uncompressed format, each compressed texel block of the source image -- is copied as a raw value to the corresponding texel of uncompressed data -- in the destination image. Thus, for example, it is legal to copy between -- a 128-bit uncompressed format and a compressed format which has a -- 128-bit sized compressed texel block representing 4×4 texels (using 8 -- bits per texel), or between a 64-bit uncompressed format and a -- compressed format which has a 64-bit sized compressed texel block -- representing 4×4 texels (using 4 bits per texel). -- -- When copying between compressed and uncompressed formats the @extent@ -- members represent the texel dimensions of the source image and not the -- destination. When copying from a compressed image to an uncompressed -- image the image texel dimensions written to the uncompressed image will -- be source extent divided by the compressed texel block dimensions. When -- copying from an uncompressed image to a compressed image the image texel -- dimensions written to the compressed image will be the source extent -- multiplied by the compressed texel block dimensions. In both cases the -- number of bytes read and the number of bytes written will be identical. -- -- Copying to or from block-compressed images is typically done in -- multiples of the compressed texel block size. For this reason the -- @extent@ /must/ be a multiple of the compressed texel block dimension. -- There is one exception to this rule which is /required/ to handle -- compressed images created with dimensions that are not a multiple of the -- compressed texel block dimensions: if the @srcImage@ is compressed, -- then: -- -- - If @extent.width@ is not a multiple of the compressed texel block -- width, then (@extent.width@ + @srcOffset.x@) /must/ equal the image -- subresource width. -- -- - If @extent.height@ is not a multiple of the compressed texel block -- height, then (@extent.height@ + @srcOffset.y@) /must/ equal the -- image subresource height. -- -- - If @extent.depth@ is not a multiple of the compressed texel block -- depth, then (@extent.depth@ + @srcOffset.z@) /must/ equal the image -- subresource depth. -- -- Similarly, if the @dstImage@ is compressed, then: -- -- - If @extent.width@ is not a multiple of the compressed texel block -- width, then (@extent.width@ + @dstOffset.x@) /must/ equal the image -- subresource width. -- -- - If @extent.height@ is not a multiple of the compressed texel block -- height, then (@extent.height@ + @dstOffset.y@) /must/ equal the -- image subresource height. -- -- - If @extent.depth@ is not a multiple of the compressed texel block -- depth, then (@extent.depth@ + @dstOffset.z@) /must/ equal the image -- subresource depth. -- -- This allows the last compressed texel block of the image in each -- non-multiple dimension to be included as a source or destination of the -- copy. -- -- “@_422@” image formats that are not -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar> -- are treated as having a 2×1 compressed texel block for the purposes of -- these rules. -- -- 'cmdCopyImage' /can/ be used to copy image data between multisample -- images, but both images /must/ have the same number of samples. -- -- == Valid Usage -- -- - If @commandBuffer@ is an unprotected command buffer, then @srcImage@ -- /must/ not be a protected image -- -- - If @commandBuffer@ is an unprotected command buffer, then @dstImage@ -- /must/ not be a protected image -- -- - If @commandBuffer@ is a protected command buffer, then @dstImage@ -- /must/ not be an unprotected image -- -- - The union of all source regions, and the union of all destination -- regions, specified by the elements of @pRegions@, /must/ not overlap -- in memory -- -- - The -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features> -- of @srcImage@ /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_SRC_BIT' -- -- - @srcImage@ /must/ have been created with -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT' -- usage flag -- -- - If @srcImage@ is non-sparse then the image or /disjoint/ plane to be -- copied /must/ be bound completely and contiguously to a single -- 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - @srcImageLayout@ /must/ specify the layout of the image subresources -- of @srcImage@ specified in @pRegions@ at the time this command is -- executed on a 'Vulkan.Core10.Handles.Device' -- -- - @srcImageLayout@ /must/ be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL', or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR' -- -- - The -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features> -- of @dstImage@ /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_TRANSFER_DST_BIT' -- -- - @dstImage@ /must/ have been created with -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT' -- usage flag -- -- - If @dstImage@ is non-sparse then the image or /disjoint/ plane that -- is the destination of the copy /must/ be bound completely and -- contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - @dstImageLayout@ /must/ specify the layout of the image subresources -- of @dstImage@ specified in @pRegions@ at the time this command is -- executed on a 'Vulkan.Core10.Handles.Device' -- -- - @dstImageLayout@ /must/ be -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL', -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL', or -- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHARED_PRESENT_KHR' -- -- - If the 'Vulkan.Core10.Enums.Format.Format' of each of @srcImage@ and -- @dstImage@ is not a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar format>, -- the 'Vulkan.Core10.Enums.Format.Format' of each of @srcImage@ and -- @dstImage@ /must/ be compatible, as defined -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies-images-format-compatibility above> -- -- - In a copy to or from a plane of a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image>, -- the 'Vulkan.Core10.Enums.Format.Format' of the image and plane -- /must/ be compatible according to -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatible-planes the description of compatible planes> -- for the plane being copied -- -- - The sample count of @srcImage@ and @dstImage@ /must/ match -- -- - The @srcSubresource.mipLevel@ member of each element of @pRegions@ -- /must/ be less than the @mipLevels@ specified in -- 'Vulkan.Core10.Image.ImageCreateInfo' when @srcImage@ was created -- -- - The @dstSubresource.mipLevel@ member of each element of @pRegions@ -- /must/ be less than the @mipLevels@ specified in -- 'Vulkan.Core10.Image.ImageCreateInfo' when @dstImage@ was created -- -- - The @srcSubresource.baseArrayLayer@ + @srcSubresource.layerCount@ of -- each element of @pRegions@ /must/ be less than or equal to the -- @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo' -- when @srcImage@ was created -- -- - The @dstSubresource.baseArrayLayer@ + @dstSubresource.layerCount@ of -- each element of @pRegions@ /must/ be less than or equal to the -- @arrayLayers@ specified in 'Vulkan.Core10.Image.ImageCreateInfo' -- when @dstImage@ was created -- -- - The @srcOffset@ and @extent@ members of each element of @pRegions@ -- /must/ respect the image transfer granularity requirements of -- @commandBuffer@’s command pool’s queue family, as described in -- 'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties' -- -- - The @dstOffset@ and @extent@ members of each element of @pRegions@ -- /must/ respect the image transfer granularity requirements of -- @commandBuffer@’s command pool’s queue family, as described in -- 'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties' -- -- - @dstImage@ and @srcImage@ /must/ not have been created with @flags@ -- containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SUBSAMPLED_BIT_EXT' -- -- - If neither @srcImage@ nor @dstImage@ has a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format> -- then for each element of @pRegions@, @srcSubresource.aspectMask@ and -- @dstSubresource.aspectMask@ /must/ match -- -- - If @srcImage@ has a 'Vulkan.Core10.Enums.Format.Format' with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion two planes> -- then for each element of @pRegions@, @srcSubresource.aspectMask@ -- /must/ be -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' -- or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' -- -- - If @srcImage@ has a 'Vulkan.Core10.Enums.Format.Format' with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion three planes> -- then for each element of @pRegions@, @srcSubresource.aspectMask@ -- /must/ be -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT', -- or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' -- -- - If @dstImage@ has a 'Vulkan.Core10.Enums.Format.Format' with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion two planes> -- then for each element of @pRegions@, @dstSubresource.aspectMask@ -- /must/ be -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT' -- or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT' -- -- - If @dstImage@ has a 'Vulkan.Core10.Enums.Format.Format' with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion three planes> -- then for each element of @pRegions@, @dstSubresource.aspectMask@ -- /must/ be -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_0_BIT', -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_1_BIT', -- or -- 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_PLANE_2_BIT' -- -- - If @srcImage@ has a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format> -- and the @dstImage@ does not have a multi-planar image format, then -- for each element of @pRegions@, @dstSubresource.aspectMask@ /must/ -- be 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' -- -- - If @dstImage@ has a -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion multi-planar image format> -- and the @srcImage@ does not have a multi-planar image format, then -- for each element of @pRegions@, @srcSubresource.aspectMask@ /must/ -- be 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT' -- -- - If @srcImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each element -- of @pRegions@, @srcSubresource.baseArrayLayer@ /must/ be @0@ and and -- @srcSubresource.layerCount@ /must/ be @1@ -- -- - If @dstImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each element -- of @pRegions@, @dstSubresource.baseArrayLayer@ /must/ be @0@ and and -- @dstSubresource.layerCount@ /must/ be @1@ -- -- - For each element of @pRegions@, @srcSubresource.aspectMask@ /must/ -- specify aspects present in @srcImage@ -- -- - For each element of @pRegions@, @dstSubresource.aspectMask@ /must/ -- specify aspects present in @dstImage@ -- -- - For each element of @pRegions@, @srcOffset.x@ and (@extent.width@ + -- @srcOffset.x@) /must/ both be greater than or equal to @0@ and less -- than or equal to the width of the specified @srcSubresource@ of -- @srcImage@ -- -- - For each element of @pRegions@, @srcOffset.y@ and (@extent.height@ + -- @srcOffset.y@) /must/ both be greater than or equal to @0@ and less -- than or equal to the height of the specified @srcSubresource@ of -- @srcImage@ -- -- - If @srcImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element -- of @pRegions@, @srcOffset.y@ /must/ be @0@ and @extent.height@ -- /must/ be @1@ -- -- - For each element of @pRegions@, @srcOffset.z@ and (@extent.depth@ + -- @srcOffset.z@) /must/ both be greater than or equal to @0@ and less -- than or equal to the depth of the specified @srcSubresource@ of -- @srcImage@ -- -- - If @srcImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element -- of @pRegions@, @srcOffset.z@ /must/ be @0@ and @extent.depth@ /must/ -- be @1@ -- -- - If @dstImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_1D', then for each element -- of @pRegions@, @dstOffset.z@ /must/ be @0@ and @extent.depth@ /must/ -- be @1@ -- -- - If @srcImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element -- of @pRegions@, @srcOffset.z@ /must/ be @0@ -- -- - If @dstImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element -- of @pRegions@, @dstOffset.z@ /must/ be @0@ -- -- - If @srcImage@ and @dstImage@ are both of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', then for each element -- of @pRegions@, @extent.depth@ /must/ be @1@ -- -- - If @srcImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', and @dstImage@ is of -- type 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each -- element of @pRegions@, @extent.depth@ /must/ equal -- @srcSubresource.layerCount@ -- -- - If @dstImage@ is of type -- 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_2D', and @srcImage@ is of -- type 'Vulkan.Core10.Enums.ImageType.IMAGE_TYPE_3D', then for each -- element of @pRegions@, @extent.depth@ /must/ equal -- @dstSubresource.layerCount@ -- -- - For each element of @pRegions@, @dstOffset.x@ and (@extent.width@ + -- @dstOffset.x@) /must/ both be greater than or equal to @0@ and less -- than or equal to the width of the specified @dstSubresource@ of -- @dstImage@ -- -- - For each element of @pRegions@, @dstOffset.y@ and (@extent.height@ + -- @dstOffset.y@) /must/ both be greater than or equal to @0@ and less -- than or equal to the height of the spec