{-# language CPP #-} -- No documentation found for Chapter "Promoted_From_VK_EXT_extended_dynamic_state" module Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state ( cmdSetCullMode , cmdSetFrontFace , cmdSetPrimitiveTopology , cmdSetViewportWithCount , cmdSetScissorWithCount , cmdBindVertexBuffers2 , cmdSetDepthTestEnable , cmdSetDepthWriteEnable , cmdSetDepthCompareOp , cmdSetDepthBoundsTestEnable , cmdSetStencilTestEnable , cmdSetStencilOp , DynamicState(..) ) where import Vulkan.Internal.Utils (traceAroundEvent) import Control.Monad (unless) import Control.Monad.IO.Class (liftIO) import Foreign.Marshal.Alloc (allocaBytes) import GHC.IO (throwIO) import GHC.Ptr (nullFunPtr) import Foreign.Ptr (nullPtr) import Foreign.Ptr (plusPtr) import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Cont (evalContT) import qualified Data.Vector (imapM_) import qualified Data.Vector (length) import qualified Data.Vector (null) import Control.Monad.IO.Class (MonadIO) import Foreign.Storable (Storable(poke)) import GHC.IO.Exception (IOErrorType(..)) import GHC.IO.Exception (IOException(..)) import Foreign.Ptr (FunPtr) import Foreign.Ptr (Ptr) import Data.Word (Word32) import Control.Monad.Trans.Cont (ContT(..)) import Data.Vector (Vector) import Vulkan.Core10.FundamentalTypes (boolToBool32) import Vulkan.NamedType ((:::)) import Vulkan.Core10.FundamentalTypes (Bool32) import Vulkan.Core10.FundamentalTypes (Bool32(..)) import Vulkan.Core10.Handles (Buffer) import Vulkan.Core10.Handles (Buffer(..)) import Vulkan.Core10.Handles (CommandBuffer) import Vulkan.Core10.Handles (CommandBuffer(..)) import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer)) import Vulkan.Core10.Handles (CommandBuffer_T) import Vulkan.Core10.Enums.CompareOp (CompareOp) import Vulkan.Core10.Enums.CompareOp (CompareOp(..)) import Vulkan.Core10.Enums.CullModeFlagBits (CullModeFlagBits(..)) import Vulkan.Core10.Enums.CullModeFlagBits (CullModeFlags) import Vulkan.Dynamic (DeviceCmds(pVkCmdBindVertexBuffers2)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetCullMode)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthBoundsTestEnable)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthCompareOp)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthTestEnable)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthWriteEnable)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetFrontFace)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetPrimitiveTopology)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetScissorWithCount)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetStencilOp)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetStencilTestEnable)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetViewportWithCount)) import Vulkan.Core10.FundamentalTypes (DeviceSize) import Vulkan.Core10.Enums.FrontFace (FrontFace) import Vulkan.Core10.Enums.FrontFace (FrontFace(..)) import Vulkan.Core10.Enums.PrimitiveTopology (PrimitiveTopology) import Vulkan.Core10.Enums.PrimitiveTopology (PrimitiveTopology(..)) import Vulkan.Core10.FundamentalTypes (Rect2D) import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlagBits(..)) import Vulkan.Core10.Enums.StencilFaceFlagBits (StencilFaceFlags) import Vulkan.Core10.Enums.StencilOp (StencilOp) import Vulkan.Core10.Enums.StencilOp (StencilOp(..)) import Vulkan.Core10.Pipeline (Viewport) import Vulkan.Core10.Enums.DynamicState (DynamicState(..)) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetCullMode :: FunPtr (Ptr CommandBuffer_T -> CullModeFlags -> IO ()) -> Ptr CommandBuffer_T -> CullModeFlags -> IO () -- | vkCmdSetCullMode - Set cull mode dynamically for a command buffer -- -- = Description -- -- This command sets the cull mode for subsequent drawing commands when -- drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CULL_MODE' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo'::@cullMode@ -- value used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetCullMode-None-08971# At least one of the following -- /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetCullMode-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetCullMode-cullMode-parameter# @cullMode@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.CullModeFlagBits.CullModeFlagBits' values -- -- - #VUID-vkCmdSetCullMode-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetCullMode-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetCullMode-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Enums.CullModeFlagBits.CullModeFlags' cmdSetCullMode :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @cullMode@ specifies the cull mode property to use for drawing. CullModeFlags -> io () cmdSetCullMode :: forall (io :: * -> *). MonadIO io => CommandBuffer -> CullModeFlags -> io () cmdSetCullMode CommandBuffer commandBuffer CullModeFlags cullMode = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetCullModePtr :: FunPtr (Ptr CommandBuffer_T -> CullModeFlags -> IO ()) vkCmdSetCullModePtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> CullModeFlags -> IO ()) pVkCmdSetCullMode (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds :: DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> CullModeFlags -> IO ()) vkCmdSetCullModePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetCullMode is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetCullMode' :: Ptr CommandBuffer_T -> CullModeFlags -> IO () vkCmdSetCullMode' = FunPtr (Ptr CommandBuffer_T -> CullModeFlags -> IO ()) -> Ptr CommandBuffer_T -> CullModeFlags -> IO () mkVkCmdSetCullMode FunPtr (Ptr CommandBuffer_T -> CullModeFlags -> IO ()) vkCmdSetCullModePtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetCullMode" (Ptr CommandBuffer_T -> CullModeFlags -> IO () vkCmdSetCullMode' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (CullModeFlags cullMode)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetFrontFace :: FunPtr (Ptr CommandBuffer_T -> FrontFace -> IO ()) -> Ptr CommandBuffer_T -> FrontFace -> IO () -- | vkCmdSetFrontFace - Set front face orientation dynamically for a command -- buffer -- -- = Description -- -- This command sets the front face orientation for subsequent drawing -- commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRONT_FACE' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo'::@frontFace@ -- value used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetFrontFace-None-08971# At least one of the following -- /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetFrontFace-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetFrontFace-frontFace-parameter# @frontFace@ /must/ be a -- valid 'Vulkan.Core10.Enums.FrontFace.FrontFace' value -- -- - #VUID-vkCmdSetFrontFace-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetFrontFace-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetFrontFace-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Enums.FrontFace.FrontFace' cmdSetFrontFace :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @frontFace@ is a 'Vulkan.Core10.Enums.FrontFace.FrontFace' value -- specifying the front-facing triangle orientation to be used for culling. FrontFace -> io () cmdSetFrontFace :: forall (io :: * -> *). MonadIO io => CommandBuffer -> FrontFace -> io () cmdSetFrontFace CommandBuffer commandBuffer FrontFace frontFace = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetFrontFacePtr :: FunPtr (Ptr CommandBuffer_T -> FrontFace -> IO ()) vkCmdSetFrontFacePtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> FrontFace -> IO ()) pVkCmdSetFrontFace (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> FrontFace -> IO ()) vkCmdSetFrontFacePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetFrontFace is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetFrontFace' :: Ptr CommandBuffer_T -> FrontFace -> IO () vkCmdSetFrontFace' = FunPtr (Ptr CommandBuffer_T -> FrontFace -> IO ()) -> Ptr CommandBuffer_T -> FrontFace -> IO () mkVkCmdSetFrontFace FunPtr (Ptr CommandBuffer_T -> FrontFace -> IO ()) vkCmdSetFrontFacePtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetFrontFace" (Ptr CommandBuffer_T -> FrontFace -> IO () vkCmdSetFrontFace' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (FrontFace frontFace)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetPrimitiveTopology :: FunPtr (Ptr CommandBuffer_T -> PrimitiveTopology -> IO ()) -> Ptr CommandBuffer_T -> PrimitiveTopology -> IO () -- | vkCmdSetPrimitiveTopology - Set primitive topology state dynamically for -- a command buffer -- -- = Description -- -- This command sets the primitive topology for subsequent drawing commands -- when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineInputAssemblyStateCreateInfo'::@topology@ -- value used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetPrimitiveTopology-None-08971# At least one of the -- following /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetPrimitiveTopology-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetPrimitiveTopology-primitiveTopology-parameter# -- @primitiveTopology@ /must/ be a valid -- 'Vulkan.Core10.Enums.PrimitiveTopology.PrimitiveTopology' value -- -- - #VUID-vkCmdSetPrimitiveTopology-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetPrimitiveTopology-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetPrimitiveTopology-videocoding# This command /must/ -- only be called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Enums.PrimitiveTopology.PrimitiveTopology' cmdSetPrimitiveTopology :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @primitiveTopology@ specifies the primitive topology to use for drawing. PrimitiveTopology -> io () cmdSetPrimitiveTopology :: forall (io :: * -> *). MonadIO io => CommandBuffer -> PrimitiveTopology -> io () cmdSetPrimitiveTopology CommandBuffer commandBuffer PrimitiveTopology primitiveTopology = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetPrimitiveTopologyPtr :: FunPtr (Ptr CommandBuffer_T -> PrimitiveTopology -> IO ()) vkCmdSetPrimitiveTopologyPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> PrimitiveTopology -> IO ()) pVkCmdSetPrimitiveTopology (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> PrimitiveTopology -> IO ()) vkCmdSetPrimitiveTopologyPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetPrimitiveTopology is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetPrimitiveTopology' :: Ptr CommandBuffer_T -> PrimitiveTopology -> IO () vkCmdSetPrimitiveTopology' = FunPtr (Ptr CommandBuffer_T -> PrimitiveTopology -> IO ()) -> Ptr CommandBuffer_T -> PrimitiveTopology -> IO () mkVkCmdSetPrimitiveTopology FunPtr (Ptr CommandBuffer_T -> PrimitiveTopology -> IO ()) vkCmdSetPrimitiveTopologyPtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetPrimitiveTopology" (Ptr CommandBuffer_T -> PrimitiveTopology -> IO () vkCmdSetPrimitiveTopology' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (PrimitiveTopology primitiveTopology)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetViewportWithCount :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr Viewport -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Viewport -> IO () -- | vkCmdSetViewportWithCount - Set the viewport count and viewports -- dynamically for a command buffer -- -- = Description -- -- This command sets the viewport count and viewports state for subsequent -- drawing commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the corresponding -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@viewportCount@ -- and @pViewports@ values used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetViewportWithCount-None-08971# At least one of the -- following /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- - #VUID-vkCmdSetViewportWithCount-viewportCount-03394# @viewportCount@ -- /must/ be between @1@ and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@, -- inclusive -- -- - #VUID-vkCmdSetViewportWithCount-viewportCount-03395# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-multiViewport multiViewport> -- feature is not enabled, @viewportCount@ /must/ be @1@ -- -- - #VUID-vkCmdSetViewportWithCount-commandBuffer-04819# @commandBuffer@ -- /must/ not have -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV'::@viewportScissor2D@ -- enabled -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetViewportWithCount-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetViewportWithCount-pViewports-parameter# @pViewports@ -- /must/ be a valid pointer to an array of @viewportCount@ valid -- 'Vulkan.Core10.Pipeline.Viewport' structures -- -- - #VUID-vkCmdSetViewportWithCount-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetViewportWithCount-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetViewportWithCount-videocoding# This command /must/ -- only be called outside of a video coding scope -- -- - #VUID-vkCmdSetViewportWithCount-viewportCount-arraylength# -- @viewportCount@ /must/ be greater than @0@ -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.Handles.CommandBuffer', 'Vulkan.Core10.Pipeline.Viewport' cmdSetViewportWithCount :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @pViewports@ specifies the viewports to use for drawing. ("viewports" ::: Vector Viewport) -> io () cmdSetViewportWithCount :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("viewports" ::: Vector Viewport) -> io () cmdSetViewportWithCount CommandBuffer commandBuffer "viewports" ::: Vector Viewport viewports = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkCmdSetViewportWithCountPtr :: FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) vkCmdSetViewportWithCountPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) pVkCmdSetViewportWithCount (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) vkCmdSetViewportWithCountPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetViewportWithCount is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetViewportWithCount' :: Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO () vkCmdSetViewportWithCount' = FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) -> Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO () mkVkCmdSetViewportWithCount FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO ()) vkCmdSetViewportWithCountPtr "pViewports" ::: Ptr Viewport pPViewports <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Viewport ((forall a. Vector a -> Int Data.Vector.length ("viewports" ::: Vector Viewport viewports)) forall a. Num a => a -> a -> a * Int 24) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i Viewport e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pViewports" ::: Ptr Viewport pPViewports forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 24 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Viewport) (Viewport e)) ("viewports" ::: Vector Viewport viewports) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetViewportWithCount" (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pViewports" ::: Ptr Viewport) -> IO () vkCmdSetViewportWithCount' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("viewports" ::: Vector Viewport viewports)) :: Word32)) ("pViewports" ::: Ptr Viewport pPViewports)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetScissorWithCount :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr Rect2D -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr Rect2D -> IO () -- | vkCmdSetScissorWithCount - Set the scissor count and scissor rectangular -- bounds dynamically for a command buffer -- -- = Description -- -- This command sets the scissor count and scissor rectangular bounds state -- for subsequent drawing commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the corresponding -- 'Vulkan.Core10.Pipeline.PipelineViewportStateCreateInfo'::@scissorCount@ -- and @pScissors@ values used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetScissorWithCount-None-08971# At least one of the -- following /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- - #VUID-vkCmdSetScissorWithCount-scissorCount-03397# @scissorCount@ -- /must/ be between @1@ and -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@, -- inclusive -- -- - #VUID-vkCmdSetScissorWithCount-scissorCount-03398# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-multiViewport multiViewport> -- feature is not enabled, @scissorCount@ /must/ be @1@ -- -- - #VUID-vkCmdSetScissorWithCount-x-03399# The @x@ and @y@ members of -- @offset@ member of any element of @pScissors@ /must/ be greater than -- or equal to @0@ -- -- - #VUID-vkCmdSetScissorWithCount-offset-03400# Evaluation of -- (@offset.x@ + @extent.width@) /must/ not cause a signed integer -- addition overflow for any element of @pScissors@ -- -- - #VUID-vkCmdSetScissorWithCount-offset-03401# Evaluation of -- (@offset.y@ + @extent.height@) /must/ not cause a signed integer -- addition overflow for any element of @pScissors@ -- -- - #VUID-vkCmdSetScissorWithCount-commandBuffer-04820# @commandBuffer@ -- /must/ not have -- 'Vulkan.Extensions.VK_NV_inherited_viewport_scissor.CommandBufferInheritanceViewportScissorInfoNV'::@viewportScissor2D@ -- enabled -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetScissorWithCount-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetScissorWithCount-pScissors-parameter# @pScissors@ -- /must/ be a valid pointer to an array of @scissorCount@ -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures -- -- - #VUID-vkCmdSetScissorWithCount-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetScissorWithCount-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetScissorWithCount-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- - #VUID-vkCmdSetScissorWithCount-scissorCount-arraylength# -- @scissorCount@ /must/ be greater than @0@ -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.FundamentalTypes.Rect2D' cmdSetScissorWithCount :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @pScissors@ specifies the scissors to use for drawing. ("scissors" ::: Vector Rect2D) -> io () cmdSetScissorWithCount :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("scissors" ::: Vector Rect2D) -> io () cmdSetScissorWithCount CommandBuffer commandBuffer "scissors" ::: Vector Rect2D scissors = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkCmdSetScissorWithCountPtr :: FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) vkCmdSetScissorWithCountPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) pVkCmdSetScissorWithCount (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) vkCmdSetScissorWithCountPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetScissorWithCount is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetScissorWithCount' :: Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO () vkCmdSetScissorWithCount' = FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) -> Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO () mkVkCmdSetScissorWithCount FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO ()) vkCmdSetScissorWithCountPtr "pScissors" ::: Ptr Rect2D pPScissors <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Rect2D ((forall a. Vector a -> Int Data.Vector.length ("scissors" ::: Vector Rect2D scissors)) forall a. Num a => a -> a -> a * Int 16) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i Rect2D e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pScissors" ::: Ptr Rect2D pPScissors forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 16 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Rect2D) (Rect2D e)) ("scissors" ::: Vector Rect2D scissors) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetScissorWithCount" (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("pScissors" ::: Ptr Rect2D) -> IO () vkCmdSetScissorWithCount' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("scissors" ::: Vector Rect2D scissors)) :: Word32)) ("pScissors" ::: Ptr Rect2D pPScissors)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdBindVertexBuffers2 :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Buffer -> Ptr DeviceSize -> Ptr DeviceSize -> Ptr DeviceSize -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Buffer -> Ptr DeviceSize -> Ptr DeviceSize -> Ptr DeviceSize -> IO () -- | vkCmdBindVertexBuffers2 - Bind vertex buffers to a command buffer and -- dynamically set strides -- -- = 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]. If @pSizes@ is not @NULL@ then @pSizes@[i] specifies the -- bound size of the vertex buffer starting from the corresponding elements -- of @pBuffers@[i] plus @pOffsets@[i]. If @pSizes@[i] is -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE' then the bound size is from -- @pBuffers@[i] plus @pOffsets@[i] to the end of the buffer @pBuffers@[i]. -- All vertex input attributes that use each of these bindings will use -- these updated addresses in their address calculations for subsequent -- drawing commands. If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is enabled, elements of @pBuffers@ /can/ be -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and /can/ be used by the -- vertex shader. If a vertex input attribute is bound to a vertex input -- binding that is 'Vulkan.Core10.APIConstants.NULL_HANDLE', the values -- taken from memory are considered to be zero, and missing G, B, or A -- components are -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fxvertex-input-extraction filled with (0,0,1)>. -- -- This command also -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#pipelines-dynamic-state dynamically sets> -- the byte strides between consecutive elements within buffer -- @pBuffers@[i] to the corresponding @pStrides@[i] value when drawing -- using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, strides are specified by the -- 'Vulkan.Core10.Pipeline.VertexInputBindingDescription'::@stride@ values -- used to create the currently active pipeline. -- -- If drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects> -- or if the bound pipeline state object was also created with the -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_EXT' -- dynamic state enabled then -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- /can/ be used instead of 'cmdBindVertexBuffers2' to set the stride. -- -- Note -- -- Unlike the static state to set the same, @pStrides@ must be between 0 -- and the maximum extent of the attributes in the binding. -- 'Vulkan.Extensions.VK_EXT_vertex_input_dynamic_state.cmdSetVertexInputEXT' -- does not have this restriction so can be used if other stride values are -- desired. -- -- == Valid Usage -- -- - #VUID-vkCmdBindVertexBuffers2-firstBinding-03355# @firstBinding@ -- /must/ be less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@ -- -- - #VUID-vkCmdBindVertexBuffers2-firstBinding-03356# The sum of -- @firstBinding@ and @bindingCount@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@ -- -- - #VUID-vkCmdBindVertexBuffers2-pOffsets-03357# If @pSizes@ is not -- @NULL@, all elements of @pOffsets@ /must/ be less than the size of -- the corresponding element in @pBuffers@ -- -- - #VUID-vkCmdBindVertexBuffers2-pSizes-03358# If @pSizes@ is not -- @NULL@, all elements of @pOffsets@ plus @pSizes@ , where @pSizes@ is -- not 'Vulkan.Core10.APIConstants.WHOLE_SIZE', /must/ be less than or -- equal to the size of the corresponding element in @pBuffers@ -- -- - #VUID-vkCmdBindVertexBuffers2-pBuffers-03359# All elements of -- @pBuffers@ /must/ have been created with the -- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_VERTEX_BUFFER_BIT' -- flag -- -- - #VUID-vkCmdBindVertexBuffers2-pBuffers-03360# Each element of -- @pBuffers@ that is non-sparse /must/ be bound completely and -- contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object -- -- - #VUID-vkCmdBindVertexBuffers2-pBuffers-04111# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-nullDescriptor nullDescriptor> -- feature is not enabled, all elements of @pBuffers@ /must/ not be -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-vkCmdBindVertexBuffers2-pBuffers-04112# If an element of -- @pBuffers@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE', then the -- corresponding element of @pOffsets@ /must/ be zero -- -- - #VUID-vkCmdBindVertexBuffers2-pStrides-03362# If @pStrides@ is not -- @NULL@ each element of @pStrides@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindingStride@ -- -- - #VUID-vkCmdBindVertexBuffers2-pStrides-06209# If @pStrides@ is not -- @NULL@ each element of @pStrides@ /must/ be either 0 or greater than -- or equal to the maximum extent of all vertex input attributes -- fetched from the corresponding binding, where the extent is -- calculated as the -- 'Vulkan.Core10.Pipeline.VertexInputAttributeDescription'::@offset@ -- plus -- 'Vulkan.Core10.Pipeline.VertexInputAttributeDescription'::@format@ -- size -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdBindVertexBuffers2-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdBindVertexBuffers2-pBuffers-parameter# @pBuffers@ /must/ -- be a valid pointer to an array of @bindingCount@ valid or -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- 'Vulkan.Core10.Handles.Buffer' handles -- -- - #VUID-vkCmdBindVertexBuffers2-pOffsets-parameter# @pOffsets@ /must/ -- be a valid pointer to an array of @bindingCount@ -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' values -- -- - #VUID-vkCmdBindVertexBuffers2-pSizes-parameter# If @pSizes@ is not -- @NULL@, @pSizes@ /must/ be a valid pointer to an array of -- @bindingCount@ 'Vulkan.Core10.FundamentalTypes.DeviceSize' values -- -- - #VUID-vkCmdBindVertexBuffers2-pStrides-parameter# If @pStrides@ is -- not @NULL@, @pStrides@ /must/ be a valid pointer to an array of -- @bindingCount@ 'Vulkan.Core10.FundamentalTypes.DeviceSize' values -- -- - #VUID-vkCmdBindVertexBuffers2-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdBindVertexBuffers2-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdBindVertexBuffers2-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- - #VUID-vkCmdBindVertexBuffers2-bindingCount-arraylength# If any of -- @pSizes@, or @pStrides@ are not @NULL@, @bindingCount@ /must/ be -- greater than @0@ -- -- - #VUID-vkCmdBindVertexBuffers2-commonparent# Both of @commandBuffer@, -- and the elements of @pBuffers@ that are valid handles of non-ignored -- parameters /must/ have been created, allocated, or retrieved from -- the same 'Vulkan.Core10.Handles.Device' -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' cmdBindVertexBuffers2 :: 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) -> -- | @pSizes@ is @NULL@ or a pointer to an array of the size in bytes of -- vertex data bound from @pBuffers@. ("sizes" ::: Vector DeviceSize) -> -- | @pStrides@ is @NULL@ or a pointer to an array of buffer strides. ("strides" ::: Vector DeviceSize) -> io () cmdBindVertexBuffers2 :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("viewportCount" ::: Word32) -> ("buffers" ::: Vector Buffer) -> ("offsets" ::: Vector DeviceSize) -> ("offsets" ::: Vector DeviceSize) -> ("offsets" ::: Vector DeviceSize) -> io () cmdBindVertexBuffers2 CommandBuffer commandBuffer "viewportCount" ::: Word32 firstBinding "buffers" ::: Vector Buffer buffers "offsets" ::: Vector DeviceSize offsets "offsets" ::: Vector DeviceSize sizes "offsets" ::: Vector DeviceSize strides = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkCmdBindVertexBuffers2Ptr :: FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("viewportCount" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> IO ()) vkCmdBindVertexBuffers2Ptr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("viewportCount" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> IO ()) pVkCmdBindVertexBuffers2 (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("viewportCount" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> IO ()) vkCmdBindVertexBuffers2Ptr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdBindVertexBuffers2 is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdBindVertexBuffers2' :: Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("viewportCount" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> IO () vkCmdBindVertexBuffers2' = FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("viewportCount" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> IO ()) -> Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("viewportCount" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> IO () mkVkCmdBindVertexBuffers2 FunPtr (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("viewportCount" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> IO ()) vkCmdBindVertexBuffers2Ptr let pBuffersLength :: Int pBuffersLength = forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("buffers" ::: Vector Buffer buffers) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless ((forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("offsets" ::: Vector DeviceSize offsets)) forall a. Eq a => a -> a -> Bool == Int pBuffersLength) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "pOffsets and pBuffers must have the same length" forall a. Maybe a Nothing forall a. Maybe a Nothing let pSizesLength :: Int pSizesLength = forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("offsets" ::: Vector DeviceSize sizes) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (forall a b. (Integral a, Num b) => a -> b fromIntegral Int pSizesLength forall a. Eq a => a -> a -> Bool == Int pBuffersLength Bool -> Bool -> Bool || Int pSizesLength forall a. Eq a => a -> a -> Bool == Int 0) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "pSizes and pBuffers must have the same length" forall a. Maybe a Nothing forall a. Maybe a Nothing let pStridesLength :: Int pStridesLength = forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ ("offsets" ::: Vector DeviceSize strides) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (forall a b. (Integral a, Num b) => a -> b fromIntegral Int pStridesLength forall a. Eq a => a -> a -> Bool == Int pBuffersLength Bool -> Bool -> Bool || Int pStridesLength forall a. Eq a => a -> a -> Bool == Int 0) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "pStrides and pBuffers must have the same length" forall a. Maybe a Nothing forall a. Maybe a Nothing "pBuffers" ::: Ptr Buffer pPBuffers <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Buffer ((forall a. Vector a -> Int Data.Vector.length ("buffers" ::: Vector Buffer buffers)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i Buffer e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pBuffers" ::: Ptr Buffer pPBuffers forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Buffer) (Buffer e)) ("buffers" ::: Vector Buffer buffers) "pOffsets" ::: Ptr DeviceSize pPOffsets <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @DeviceSize ((forall a. Vector a -> Int Data.Vector.length ("offsets" ::: Vector DeviceSize offsets)) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i DeviceSize e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pOffsets" ::: Ptr DeviceSize pPOffsets forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr DeviceSize) (DeviceSize e)) ("offsets" ::: Vector DeviceSize offsets) "pOffsets" ::: Ptr DeviceSize pSizes <- if forall a. Vector a -> Bool Data.Vector.null ("offsets" ::: Vector DeviceSize sizes) then forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr else do "pOffsets" ::: Ptr DeviceSize pPSizes <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @DeviceSize (((forall a. Vector a -> Int Data.Vector.length ("offsets" ::: Vector DeviceSize sizes))) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i DeviceSize e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pOffsets" ::: Ptr DeviceSize pPSizes forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr DeviceSize) (DeviceSize e)) (("offsets" ::: Vector DeviceSize sizes)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ "pOffsets" ::: Ptr DeviceSize pPSizes "pOffsets" ::: Ptr DeviceSize pStrides <- if forall a. Vector a -> Bool Data.Vector.null ("offsets" ::: Vector DeviceSize strides) then forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr else do "pOffsets" ::: Ptr DeviceSize pPStrides <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @DeviceSize (((forall a. Vector a -> Int Data.Vector.length ("offsets" ::: Vector DeviceSize strides))) forall a. Num a => a -> a -> a * Int 8) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i DeviceSize e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pOffsets" ::: Ptr DeviceSize pPStrides forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 8 forall a. Num a => a -> a -> a * (Int i)) :: Ptr DeviceSize) (DeviceSize e)) (("offsets" ::: Vector DeviceSize strides)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ "pOffsets" ::: Ptr DeviceSize pPStrides forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdBindVertexBuffers2" (Ptr CommandBuffer_T -> ("viewportCount" ::: Word32) -> ("viewportCount" ::: Word32) -> ("pBuffers" ::: Ptr Buffer) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> ("pOffsets" ::: Ptr DeviceSize) -> IO () vkCmdBindVertexBuffers2' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("viewportCount" ::: Word32 firstBinding) ((forall a b. (Integral a, Num b) => a -> b fromIntegral Int pBuffersLength :: Word32)) ("pBuffers" ::: Ptr Buffer pPBuffers) ("pOffsets" ::: Ptr DeviceSize pPOffsets) "pOffsets" ::: Ptr DeviceSize pSizes "pOffsets" ::: Ptr DeviceSize pStrides) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetDepthTestEnable :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO () -- | vkCmdSetDepthTestEnable - Set depth test enable dynamically for a -- command buffer -- -- = Description -- -- This command sets the depth test enable for subsequent drawing commands -- when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_TEST_ENABLE' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@depthTestEnable@ -- value used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetDepthTestEnable-None-08971# At least one of the -- following /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetDepthTestEnable-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetDepthTestEnable-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetDepthTestEnable-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetDepthTestEnable-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.FundamentalTypes.Bool32', -- 'Vulkan.Core10.Handles.CommandBuffer' cmdSetDepthTestEnable :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @depthTestEnable@ specifies if the depth test is enabled. ("depthTestEnable" ::: Bool) -> io () cmdSetDepthTestEnable :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io () cmdSetDepthTestEnable CommandBuffer commandBuffer Bool depthTestEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetDepthTestEnablePtr :: FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetDepthTestEnablePtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) pVkCmdSetDepthTestEnable (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetDepthTestEnablePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetDepthTestEnable is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetDepthTestEnable' :: Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () vkCmdSetDepthTestEnable' = FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) -> Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () mkVkCmdSetDepthTestEnable FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetDepthTestEnablePtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetDepthTestEnable" (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () vkCmdSetDepthTestEnable' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Bool -> "depthTestEnable" ::: Bool32 boolToBool32 (Bool depthTestEnable))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetDepthWriteEnable :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO () -- | vkCmdSetDepthWriteEnable - Set depth write enable dynamically for a -- command buffer -- -- = Description -- -- This command sets the depth write enable for subsequent drawing commands -- when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@depthWriteEnable@ -- value used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetDepthWriteEnable-None-08971# At least one of the -- following /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetDepthWriteEnable-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetDepthWriteEnable-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetDepthWriteEnable-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetDepthWriteEnable-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.FundamentalTypes.Bool32', -- 'Vulkan.Core10.Handles.CommandBuffer' cmdSetDepthWriteEnable :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @depthWriteEnable@ specifies if depth writes are enabled. ("depthWriteEnable" ::: Bool) -> io () cmdSetDepthWriteEnable :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io () cmdSetDepthWriteEnable CommandBuffer commandBuffer Bool depthWriteEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetDepthWriteEnablePtr :: FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetDepthWriteEnablePtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) pVkCmdSetDepthWriteEnable (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetDepthWriteEnablePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetDepthWriteEnable is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetDepthWriteEnable' :: Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () vkCmdSetDepthWriteEnable' = FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) -> Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () mkVkCmdSetDepthWriteEnable FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetDepthWriteEnablePtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetDepthWriteEnable" (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () vkCmdSetDepthWriteEnable' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Bool -> "depthTestEnable" ::: Bool32 boolToBool32 (Bool depthWriteEnable))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetDepthCompareOp :: FunPtr (Ptr CommandBuffer_T -> CompareOp -> IO ()) -> Ptr CommandBuffer_T -> CompareOp -> IO () -- | vkCmdSetDepthCompareOp - Set depth comparison operator dynamically for a -- command buffer -- -- = Description -- -- This command sets the depth comparison operator for subsequent drawing -- commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_COMPARE_OP' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@depthCompareOp@ -- value used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetDepthCompareOp-None-08971# At least one of the -- following /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetDepthCompareOp-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetDepthCompareOp-depthCompareOp-parameter# -- @depthCompareOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.CompareOp.CompareOp' value -- -- - #VUID-vkCmdSetDepthCompareOp-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetDepthCompareOp-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetDepthCompareOp-videocoding# This command /must/ only -- be called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Enums.CompareOp.CompareOp' cmdSetDepthCompareOp :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @depthCompareOp@ is a 'Vulkan.Core10.Enums.CompareOp.CompareOp' value -- specifying the comparison operator used for the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#fragops-depth-comparison Depth Comparison> -- step of the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#fragops-depth depth test>. ("depthCompareOp" ::: CompareOp) -> io () cmdSetDepthCompareOp :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("depthCompareOp" ::: CompareOp) -> io () cmdSetDepthCompareOp CommandBuffer commandBuffer "depthCompareOp" ::: CompareOp depthCompareOp = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetDepthCompareOpPtr :: FunPtr (Ptr CommandBuffer_T -> ("depthCompareOp" ::: CompareOp) -> IO ()) vkCmdSetDepthCompareOpPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("depthCompareOp" ::: CompareOp) -> IO ()) pVkCmdSetDepthCompareOp (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("depthCompareOp" ::: CompareOp) -> IO ()) vkCmdSetDepthCompareOpPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetDepthCompareOp is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetDepthCompareOp' :: Ptr CommandBuffer_T -> ("depthCompareOp" ::: CompareOp) -> IO () vkCmdSetDepthCompareOp' = FunPtr (Ptr CommandBuffer_T -> ("depthCompareOp" ::: CompareOp) -> IO ()) -> Ptr CommandBuffer_T -> ("depthCompareOp" ::: CompareOp) -> IO () mkVkCmdSetDepthCompareOp FunPtr (Ptr CommandBuffer_T -> ("depthCompareOp" ::: CompareOp) -> IO ()) vkCmdSetDepthCompareOpPtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetDepthCompareOp" (Ptr CommandBuffer_T -> ("depthCompareOp" ::: CompareOp) -> IO () vkCmdSetDepthCompareOp' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("depthCompareOp" ::: CompareOp depthCompareOp)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetDepthBoundsTestEnable :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO () -- | vkCmdSetDepthBoundsTestEnable - Set depth bounds test enable dynamically -- for a command buffer -- -- = Description -- -- This command sets the depth bounds enable for subsequent drawing -- commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE' -- set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@depthBoundsTestEnable@ -- value used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetDepthBoundsTestEnable-None-08971# At least one of the -- following /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetDepthBoundsTestEnable-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetDepthBoundsTestEnable-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetDepthBoundsTestEnable-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetDepthBoundsTestEnable-videocoding# This command /must/ -- only be called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.FundamentalTypes.Bool32', -- 'Vulkan.Core10.Handles.CommandBuffer' cmdSetDepthBoundsTestEnable :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @depthBoundsTestEnable@ specifies if the depth bounds test is enabled. ("depthBoundsTestEnable" ::: Bool) -> io () cmdSetDepthBoundsTestEnable :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io () cmdSetDepthBoundsTestEnable CommandBuffer commandBuffer Bool depthBoundsTestEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetDepthBoundsTestEnablePtr :: FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetDepthBoundsTestEnablePtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) pVkCmdSetDepthBoundsTestEnable (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetDepthBoundsTestEnablePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetDepthBoundsTestEnable is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetDepthBoundsTestEnable' :: Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () vkCmdSetDepthBoundsTestEnable' = FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) -> Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () mkVkCmdSetDepthBoundsTestEnable FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetDepthBoundsTestEnablePtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetDepthBoundsTestEnable" (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () vkCmdSetDepthBoundsTestEnable' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Bool -> "depthTestEnable" ::: Bool32 boolToBool32 (Bool depthBoundsTestEnable))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetStencilTestEnable :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO () -- | vkCmdSetStencilTestEnable - Set stencil test enable dynamically for a -- command buffer -- -- = Description -- -- This command sets the stencil test enable for subsequent drawing -- commands when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_TEST_ENABLE' set -- in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@stencilTestEnable@ -- value used to create the currently active pipeline. -- -- == Valid Usage -- -- - #VUID-vkCmdSetStencilTestEnable-None-08971# At least one of the -- following /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetStencilTestEnable-commandBuffer-parameter# -- @commandBuffer@ /must/ be a valid -- 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetStencilTestEnable-commandBuffer-recording# -- @commandBuffer@ /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetStencilTestEnable-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetStencilTestEnable-videocoding# This command /must/ -- only be called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.FundamentalTypes.Bool32', -- 'Vulkan.Core10.Handles.CommandBuffer' cmdSetStencilTestEnable :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @stencilTestEnable@ specifies if the stencil test is enabled. ("stencilTestEnable" ::: Bool) -> io () cmdSetStencilTestEnable :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io () cmdSetStencilTestEnable CommandBuffer commandBuffer Bool stencilTestEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetStencilTestEnablePtr :: FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetStencilTestEnablePtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) pVkCmdSetStencilTestEnable (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetStencilTestEnablePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetStencilTestEnable is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetStencilTestEnable' :: Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () vkCmdSetStencilTestEnable' = FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) -> Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () mkVkCmdSetStencilTestEnable FunPtr (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO ()) vkCmdSetStencilTestEnablePtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetStencilTestEnable" (Ptr CommandBuffer_T -> ("depthTestEnable" ::: Bool32) -> IO () vkCmdSetStencilTestEnable' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) (Bool -> "depthTestEnable" ::: Bool32 boolToBool32 (Bool stencilTestEnable))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetStencilOp :: FunPtr (Ptr CommandBuffer_T -> StencilFaceFlags -> StencilOp -> StencilOp -> StencilOp -> CompareOp -> IO ()) -> Ptr CommandBuffer_T -> StencilFaceFlags -> StencilOp -> StencilOp -> StencilOp -> CompareOp -> IO () -- | vkCmdSetStencilOp - Set stencil operation dynamically for a command -- buffer -- -- = Description -- -- This command sets the stencil operation for subsequent drawing commands -- when when drawing using -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#shaders-objects shader objects>, -- or when the graphics pipeline is created with -- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_OP' set in -- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@. -- Otherwise, this state is specified by the corresponding -- 'Vulkan.Core10.Pipeline.PipelineDepthStencilStateCreateInfo'::@failOp@, -- @passOp@, @depthFailOp@, and @compareOp@ values used to create the -- currently active pipeline, for both front and back faces. -- -- == Valid Usage -- -- - #VUID-vkCmdSetStencilOp-None-08971# At least one of the following -- /must/ be true: -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState> -- feature is enabled -- -- - the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is enabled -- -- - the value of -- 'Vulkan.Core10.DeviceInitialization.ApplicationInfo'::@apiVersion@ -- used to create the 'Vulkan.Core10.Handles.Instance' parent of -- @commandBuffer@ is greater than or equal to Version 1.3 -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetStencilOp-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetStencilOp-faceMask-parameter# @faceMask@ /must/ be a -- valid combination of -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlagBits' values -- -- - #VUID-vkCmdSetStencilOp-faceMask-requiredbitmask# @faceMask@ /must/ -- not be @0@ -- -- - #VUID-vkCmdSetStencilOp-failOp-parameter# @failOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.StencilOp.StencilOp' value -- -- - #VUID-vkCmdSetStencilOp-passOp-parameter# @passOp@ /must/ be a valid -- 'Vulkan.Core10.Enums.StencilOp.StencilOp' value -- -- - #VUID-vkCmdSetStencilOp-depthFailOp-parameter# @depthFailOp@ /must/ -- be a valid 'Vulkan.Core10.Enums.StencilOp.StencilOp' value -- -- - #VUID-vkCmdSetStencilOp-compareOp-parameter# @compareOp@ /must/ be a -- valid 'Vulkan.Core10.Enums.CompareOp.CompareOp' value -- -- - #VUID-vkCmdSetStencilOp-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetStencilOp-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics operations -- -- - #VUID-vkCmdSetStencilOp-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Outside | Graphics | State | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state VK_EXT_extended_dynamic_state>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>, -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_3 VK_VERSION_1_3>, -- 'Vulkan.Core10.Handles.CommandBuffer', -- 'Vulkan.Core10.Enums.CompareOp.CompareOp', -- 'Vulkan.Core10.Enums.StencilFaceFlagBits.StencilFaceFlags', -- 'Vulkan.Core10.Enums.StencilOp.StencilOp' cmdSetStencilOp :: 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 stencil operation. ("faceMask" ::: StencilFaceFlags) -> -- | @failOp@ is a 'Vulkan.Core10.Enums.StencilOp.StencilOp' value specifying -- the action performed on samples that fail the stencil test. ("failOp" ::: StencilOp) -> -- | @passOp@ is a 'Vulkan.Core10.Enums.StencilOp.StencilOp' value specifying -- the action performed on samples that pass both the depth and stencil -- tests. ("passOp" ::: StencilOp) -> -- | @depthFailOp@ is a 'Vulkan.Core10.Enums.StencilOp.StencilOp' value -- specifying the action performed on samples that pass the stencil test -- and fail the depth test. ("depthFailOp" ::: StencilOp) -> -- | @compareOp@ is a 'Vulkan.Core10.Enums.CompareOp.CompareOp' value -- specifying the comparison operator used in the stencil test. CompareOp -> io () cmdSetStencilOp :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("faceMask" ::: StencilFaceFlags) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("depthCompareOp" ::: CompareOp) -> io () cmdSetStencilOp CommandBuffer commandBuffer "faceMask" ::: StencilFaceFlags faceMask "failOp" ::: StencilOp failOp "failOp" ::: StencilOp passOp "failOp" ::: StencilOp depthFailOp "depthCompareOp" ::: CompareOp compareOp = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetStencilOpPtr :: FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("depthCompareOp" ::: CompareOp) -> IO ()) vkCmdSetStencilOpPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("depthCompareOp" ::: CompareOp) -> IO ()) pVkCmdSetStencilOp (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("depthCompareOp" ::: CompareOp) -> IO ()) vkCmdSetStencilOpPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetStencilOp is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetStencilOp' :: Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("depthCompareOp" ::: CompareOp) -> IO () vkCmdSetStencilOp' = FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("depthCompareOp" ::: CompareOp) -> IO ()) -> Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("depthCompareOp" ::: CompareOp) -> IO () mkVkCmdSetStencilOp FunPtr (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("depthCompareOp" ::: CompareOp) -> IO ()) vkCmdSetStencilOpPtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetStencilOp" (Ptr CommandBuffer_T -> ("faceMask" ::: StencilFaceFlags) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("failOp" ::: StencilOp) -> ("depthCompareOp" ::: CompareOp) -> IO () vkCmdSetStencilOp' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("faceMask" ::: StencilFaceFlags faceMask) ("failOp" ::: StencilOp failOp) ("failOp" ::: StencilOp passOp) ("failOp" ::: StencilOp depthFailOp) ("depthCompareOp" ::: CompareOp compareOp)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ()