{-# language CPP #-}
-- | = Name
--
-- VK_EXT_extended_dynamic_state3 - device extension
--
-- == VK_EXT_extended_dynamic_state3
--
-- [__Name String__]
--     @VK_EXT_extended_dynamic_state3@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     456
--
-- [__Revision__]
--     2
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_get_physical_device_properties2@ to be enabled
--         for any device-level functionality
--
-- [__Contact__]
--
--     -   Piers Daniell
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_extended_dynamic_state3] @pdaniell-nv%0A*Here describe the issue or question you have about the VK_EXT_extended_dynamic_state3 extension* >
--
-- [__Extension Proposal__]
--     <https://github.com/KhronosGroup/Vulkan-Docs/tree/main/proposals/VK_EXT_extended_dynamic_state3.adoc VK_EXT_extended_dynamic_state3>
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2022-09-02
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Daniel Story, Nintendo
--
--     -   Jamie Madill, Google
--
--     -   Jan-Harald Fredriksen, Arm
--
--     -   Jason Ekstrand, Collabora
--
--     -   Mike Blumenkrantz, Valve
--
--     -   Ricardo Garcia, Igalia
--
--     -   Samuel Pitoiset, Valve
--
--     -   Shahbaz Youssefi, Google
--
--     -   Stu Smith, AMD
--
--     -   Tapani Pälli, Intel
--
-- == Description
--
-- This extension adds almost all of the remaining pipeline state as
-- dynamic state to help applications further reduce the number of
-- monolithic pipelines they need to create and bind.
--
-- == New Commands
--
-- -   'cmdSetAlphaToCoverageEnableEXT'
--
-- -   'cmdSetAlphaToOneEnableEXT'
--
-- -   'cmdSetColorBlendAdvancedEXT'
--
-- -   'cmdSetColorBlendEnableEXT'
--
-- -   'cmdSetColorBlendEquationEXT'
--
-- -   'cmdSetColorWriteMaskEXT'
--
-- -   'cmdSetConservativeRasterizationModeEXT'
--
-- -   'cmdSetCoverageModulationModeNV'
--
-- -   'cmdSetCoverageModulationTableEnableNV'
--
-- -   'cmdSetCoverageModulationTableNV'
--
-- -   'cmdSetCoverageReductionModeNV'
--
-- -   'cmdSetCoverageToColorEnableNV'
--
-- -   'cmdSetCoverageToColorLocationNV'
--
-- -   'cmdSetDepthClampEnableEXT'
--
-- -   'cmdSetDepthClipEnableEXT'
--
-- -   'cmdSetDepthClipNegativeOneToOneEXT'
--
-- -   'cmdSetExtraPrimitiveOverestimationSizeEXT'
--
-- -   'cmdSetLineRasterizationModeEXT'
--
-- -   'cmdSetLineStippleEnableEXT'
--
-- -   'cmdSetLogicOpEnableEXT'
--
-- -   'cmdSetPolygonModeEXT'
--
-- -   'cmdSetProvokingVertexModeEXT'
--
-- -   'cmdSetRasterizationSamplesEXT'
--
-- -   'cmdSetRasterizationStreamEXT'
--
-- -   'cmdSetRepresentativeFragmentTestEnableNV'
--
-- -   'cmdSetSampleLocationsEnableEXT'
--
-- -   'cmdSetSampleMaskEXT'
--
-- -   'cmdSetShadingRateImageEnableNV'
--
-- -   'cmdSetTessellationDomainOriginEXT'
--
-- -   'cmdSetViewportSwizzleNV'
--
-- -   'cmdSetViewportWScalingEnableNV'
--
-- == New Structures
--
-- -   'ColorBlendAdvancedEXT'
--
-- -   'ColorBlendEquationEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceExtendedDynamicState3FeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceExtendedDynamicState3PropertiesEXT'
--
-- == New Enum Constants
--
-- -   'EXT_EXTENDED_DYNAMIC_STATE_3_EXTENSION_NAME'
--
-- -   'EXT_EXTENDED_DYNAMIC_STATE_3_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.DynamicState.DynamicState':
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_ONE_ENABLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_MODE_NV'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_NV'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_REDUCTION_MODE_NV'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_LOCATION_NV'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLAMP_ENABLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_ENABLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_NEGATIVE_ONE_TO_ONE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXTRA_PRIMITIVE_OVERESTIMATION_SIZE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_ENABLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_POLYGON_MODE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PROVOKING_VERTEX_MODE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_REPRESENTATIVE_FRAGMENT_TEST_ENABLE_NV'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SHADING_RATE_IMAGE_ENABLE_NV'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_TESSELLATION_DOMAIN_ORIGIN_EXT'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV'
--
--     -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_ENABLE_NV'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_3_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_3_PROPERTIES_EXT'
--
-- == Issues
--
-- 1) What about the VkPipelineMultisampleStateCreateInfo state
-- @sampleShadingEnable@ and @minSampleShading@?
--
-- [UNRESOLVED]
--
--     -   @sampleShadingEnable@ and @minSampleShading@ are required when
--         compiling the fragment shader, and it is not meaningful to set
--         them dynamically since they always need to match the fragment
--         shader state, so this hardware state may as well just come from
--         the pipeline with the fragment shader.
--
-- == Version History
--
-- -   Revision 2, 2022-07-18 (Piers Daniell)
--
--     -   Added rasterizationSamples
--
-- -   Revision 1, 2022-05-18 (Piers Daniell)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'ColorBlendAdvancedEXT', 'ColorBlendEquationEXT',
-- 'PhysicalDeviceExtendedDynamicState3FeaturesEXT',
-- 'PhysicalDeviceExtendedDynamicState3PropertiesEXT',
-- 'cmdSetAlphaToCoverageEnableEXT', 'cmdSetAlphaToOneEnableEXT',
-- 'cmdSetColorBlendAdvancedEXT', 'cmdSetColorBlendEnableEXT',
-- 'cmdSetColorBlendEquationEXT', 'cmdSetColorWriteMaskEXT',
-- 'cmdSetConservativeRasterizationModeEXT',
-- 'cmdSetCoverageModulationModeNV',
-- 'cmdSetCoverageModulationTableEnableNV',
-- 'cmdSetCoverageModulationTableNV', 'cmdSetCoverageReductionModeNV',
-- 'cmdSetCoverageToColorEnableNV', 'cmdSetCoverageToColorLocationNV',
-- 'cmdSetDepthClampEnableEXT', 'cmdSetDepthClipEnableEXT',
-- 'cmdSetDepthClipNegativeOneToOneEXT',
-- 'cmdSetExtraPrimitiveOverestimationSizeEXT',
-- 'cmdSetLineRasterizationModeEXT', 'cmdSetLineStippleEnableEXT',
-- 'cmdSetLogicOpEnableEXT', 'cmdSetPolygonModeEXT',
-- 'cmdSetProvokingVertexModeEXT', 'cmdSetRasterizationSamplesEXT',
-- 'cmdSetRasterizationStreamEXT',
-- 'cmdSetRepresentativeFragmentTestEnableNV',
-- 'cmdSetSampleLocationsEnableEXT', 'cmdSetSampleMaskEXT',
-- 'cmdSetShadingRateImageEnableNV', 'cmdSetTessellationDomainOriginEXT',
-- 'cmdSetViewportSwizzleNV', 'cmdSetViewportWScalingEnableNV'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state3 Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_extended_dynamic_state3  ( cmdSetTessellationDomainOriginEXT
                                                         , cmdSetDepthClampEnableEXT
                                                         , cmdSetPolygonModeEXT
                                                         , cmdSetRasterizationSamplesEXT
                                                         , cmdSetSampleMaskEXT
                                                         , cmdSetAlphaToCoverageEnableEXT
                                                         , cmdSetAlphaToOneEnableEXT
                                                         , cmdSetLogicOpEnableEXT
                                                         , cmdSetColorBlendEnableEXT
                                                         , cmdSetColorBlendEquationEXT
                                                         , cmdSetColorWriteMaskEXT
                                                         , cmdSetRasterizationStreamEXT
                                                         , cmdSetConservativeRasterizationModeEXT
                                                         , cmdSetExtraPrimitiveOverestimationSizeEXT
                                                         , cmdSetDepthClipEnableEXT
                                                         , cmdSetSampleLocationsEnableEXT
                                                         , cmdSetColorBlendAdvancedEXT
                                                         , cmdSetProvokingVertexModeEXT
                                                         , cmdSetLineRasterizationModeEXT
                                                         , cmdSetLineStippleEnableEXT
                                                         , cmdSetDepthClipNegativeOneToOneEXT
                                                         , cmdSetViewportWScalingEnableNV
                                                         , cmdSetViewportSwizzleNV
                                                         , cmdSetCoverageToColorEnableNV
                                                         , cmdSetCoverageToColorLocationNV
                                                         , cmdSetCoverageModulationModeNV
                                                         , cmdSetCoverageModulationTableEnableNV
                                                         , cmdSetCoverageModulationTableNV
                                                         , cmdSetShadingRateImageEnableNV
                                                         , cmdSetCoverageReductionModeNV
                                                         , cmdSetRepresentativeFragmentTestEnableNV
                                                         , PhysicalDeviceExtendedDynamicState3FeaturesEXT(..)
                                                         , PhysicalDeviceExtendedDynamicState3PropertiesEXT(..)
                                                         , ColorBlendEquationEXT(..)
                                                         , ColorBlendAdvancedEXT(..)
                                                         , EXT_EXTENDED_DYNAMIC_STATE_3_SPEC_VERSION
                                                         , pattern EXT_EXTENDED_DYNAMIC_STATE_3_SPEC_VERSION
                                                         , EXT_EXTENDED_DYNAMIC_STATE_3_EXTENSION_NAME
                                                         , pattern EXT_EXTENDED_DYNAMIC_STATE_3_EXTENSION_NAME
                                                         , ViewportSwizzleNV(..)
                                                         , ViewportCoordinateSwizzleNV(..)
                                                         , BlendOverlapEXT(..)
                                                         , CoverageModulationModeNV(..)
                                                         , CoverageReductionModeNV(..)
                                                         , ConservativeRasterizationModeEXT(..)
                                                         , LineRasterizationModeEXT(..)
                                                         , ProvokingVertexModeEXT(..)
                                                         ) 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 Foreign.C.Types (CFloat(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(CFloat))
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Enums.BlendFactor (BlendFactor)
import Vulkan.Core10.Enums.BlendOp (BlendOp)
import Vulkan.Extensions.VK_EXT_blend_operation_advanced (BlendOverlapEXT)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (Bool32(..))
import Vulkan.Core10.Enums.ColorComponentFlagBits (ColorComponentFlagBits(..))
import Vulkan.Core10.Enums.ColorComponentFlagBits (ColorComponentFlags)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Extensions.VK_EXT_conservative_rasterization (ConservativeRasterizationModeEXT)
import Vulkan.Extensions.VK_EXT_conservative_rasterization (ConservativeRasterizationModeEXT(..))
import Vulkan.Extensions.VK_NV_framebuffer_mixed_samples (CoverageModulationModeNV)
import Vulkan.Extensions.VK_NV_framebuffer_mixed_samples (CoverageModulationModeNV(..))
import Vulkan.Extensions.VK_NV_coverage_reduction_mode (CoverageReductionModeNV)
import Vulkan.Extensions.VK_NV_coverage_reduction_mode (CoverageReductionModeNV(..))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetAlphaToCoverageEnableEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetAlphaToOneEnableEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetColorBlendAdvancedEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetColorBlendEnableEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetColorBlendEquationEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetColorWriteMaskEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetConservativeRasterizationModeEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetCoverageModulationModeNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetCoverageModulationTableEnableNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetCoverageModulationTableNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetCoverageReductionModeNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetCoverageToColorEnableNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetCoverageToColorLocationNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthClampEnableEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthClipEnableEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDepthClipNegativeOneToOneEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetExtraPrimitiveOverestimationSizeEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetLineRasterizationModeEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetLineStippleEnableEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetLogicOpEnableEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetPolygonModeEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetProvokingVertexModeEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetRasterizationSamplesEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetRasterizationStreamEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetRepresentativeFragmentTestEnableNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetSampleLocationsEnableEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetSampleMaskEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetShadingRateImageEnableNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetTessellationDomainOriginEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetViewportSwizzleNV))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetViewportWScalingEnableNV))
import Vulkan.Extensions.VK_EXT_line_rasterization (LineRasterizationModeEXT)
import Vulkan.Extensions.VK_EXT_line_rasterization (LineRasterizationModeEXT(..))
import Vulkan.Core10.Enums.PolygonMode (PolygonMode)
import Vulkan.Core10.Enums.PolygonMode (PolygonMode(..))
import Vulkan.Extensions.VK_EXT_provoking_vertex (ProvokingVertexModeEXT)
import Vulkan.Extensions.VK_EXT_provoking_vertex (ProvokingVertexModeEXT(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits(..))
import Vulkan.Core10.FundamentalTypes (SampleMask)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core11.Enums.TessellationDomainOrigin (TessellationDomainOrigin)
import Vulkan.Core11.Enums.TessellationDomainOrigin (TessellationDomainOrigin(..))
import Vulkan.Extensions.VK_NV_viewport_swizzle (ViewportSwizzleNV)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_3_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_3_PROPERTIES_EXT))
import Vulkan.Extensions.VK_EXT_blend_operation_advanced (BlendOverlapEXT(..))
import Vulkan.Extensions.VK_EXT_conservative_rasterization (ConservativeRasterizationModeEXT(..))
import Vulkan.Extensions.VK_NV_framebuffer_mixed_samples (CoverageModulationModeNV(..))
import Vulkan.Extensions.VK_NV_coverage_reduction_mode (CoverageReductionModeNV(..))
import Vulkan.Extensions.VK_EXT_line_rasterization (LineRasterizationModeEXT(..))
import Vulkan.Extensions.VK_EXT_provoking_vertex (ProvokingVertexModeEXT(..))
import Vulkan.Extensions.VK_NV_viewport_swizzle (ViewportCoordinateSwizzleNV(..))
import Vulkan.Extensions.VK_NV_viewport_swizzle (ViewportSwizzleNV(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdSetTessellationDomainOriginEXT
  :: FunPtr (Ptr CommandBuffer_T -> TessellationDomainOrigin -> IO ()) -> Ptr CommandBuffer_T -> TessellationDomainOrigin -> IO ()

-- | vkCmdSetTessellationDomainOriginEXT - Specify the origin of the
-- tessellation domain space dynamically for a command buffer
--
-- = Description
--
-- This command sets the origin of the tessellation domain space for
-- subsequent drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_TESSELLATION_DOMAIN_ORIGIN_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.PipelineTessellationDomainOriginStateCreateInfo'::@domainOrigin@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetTessellationDomainOriginEXT-extendedDynamicState3TessellationDomainOrigin-07444#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3TessellationDomainOrigin extendedDynamicState3TessellationDomainOrigin>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetTessellationDomainOriginEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetTessellationDomainOriginEXT-domainOrigin-parameter#
--     @domainOrigin@ /must/ be a valid
--     'Vulkan.Core11.Enums.TessellationDomainOrigin.TessellationDomainOrigin'
--     value
--
-- -   #VUID-vkCmdSetTessellationDomainOriginEXT-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-vkCmdSetTessellationDomainOriginEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetTessellationDomainOriginEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core11.Enums.TessellationDomainOrigin.TessellationDomainOrigin'
cmdSetTessellationDomainOriginEXT :: forall io
                                   . (MonadIO io)
                                  => -- | @commandBuffer@ is the command buffer into which the command will be
                                     -- recorded.
                                     CommandBuffer
                                  -> -- | @domainOrigin@ specifies the origin of the tessellation domain space.
                                     TessellationDomainOrigin
                                  -> io ()
cmdSetTessellationDomainOriginEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> TessellationDomainOrigin -> io ()
cmdSetTessellationDomainOriginEXT CommandBuffer
commandBuffer TessellationDomainOrigin
domainOrigin = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetTessellationDomainOriginEXTPtr :: FunPtr (Ptr CommandBuffer_T -> TessellationDomainOrigin -> IO ())
vkCmdSetTessellationDomainOriginEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> TessellationDomainOrigin -> IO ())
pVkCmdSetTessellationDomainOriginEXT (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 -> TessellationDomainOrigin -> IO ())
vkCmdSetTessellationDomainOriginEXTPtr 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 vkCmdSetTessellationDomainOriginEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetTessellationDomainOriginEXT' :: Ptr CommandBuffer_T -> TessellationDomainOrigin -> IO ()
vkCmdSetTessellationDomainOriginEXT' = FunPtr (Ptr CommandBuffer_T -> TessellationDomainOrigin -> IO ())
-> Ptr CommandBuffer_T -> TessellationDomainOrigin -> IO ()
mkVkCmdSetTessellationDomainOriginEXT FunPtr (Ptr CommandBuffer_T -> TessellationDomainOrigin -> IO ())
vkCmdSetTessellationDomainOriginEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetTessellationDomainOriginEXT" (Ptr CommandBuffer_T -> TessellationDomainOrigin -> IO ()
vkCmdSetTessellationDomainOriginEXT'
                                                            (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                            (TessellationDomainOrigin
domainOrigin))
  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" mkVkCmdSetDepthClampEnableEXT
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetDepthClampEnableEXT - Specify dynamically whether depth clamping
-- is enabled in the command buffer
--
-- = Description
--
-- This command sets whether depth clamping is enabled or disabled for
-- subsequent drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLAMP_ENABLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo'::@depthClampEnable@
-- value used to create the currently active pipeline.
--
-- If the depth clamping state is changed dynamically, and the pipeline was
-- not created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_ENABLE_EXT'
-- enabled, then depth clipping is enabled when depth clamping is disabled
-- and vice versa.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetDepthClampEnableEXT-extendedDynamicState3DepthClampEnable-07448#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3DepthClampEnable extendedDynamicState3DepthClampEnable>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetDepthClampEnableEXT-depthClamp-07449# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-depthClamp depthClamp>
--     feature is not enabled, @depthClampEnable@ must be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetDepthClampEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetDepthClampEnableEXT-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-vkCmdSetDepthClampEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetDepthClampEnableEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetDepthClampEnableEXT :: forall io
                           . (MonadIO io)
                          => -- | @commandBuffer@ is the command buffer into which the command will be
                             -- recorded.
                             CommandBuffer
                          -> -- | @depthClampEnable@ specifies whether depth clamping is enabled.
                             ("depthClampEnable" ::: Bool)
                          -> io ()
cmdSetDepthClampEnableEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetDepthClampEnableEXT CommandBuffer
commandBuffer Bool
depthClampEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetDepthClampEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetDepthClampEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetDepthClampEnableEXT (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetDepthClampEnableEXTPtr 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 vkCmdSetDepthClampEnableEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetDepthClampEnableEXT' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetDepthClampEnableEXT' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetDepthClampEnableEXT FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetDepthClampEnableEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetDepthClampEnableEXT" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetDepthClampEnableEXT'
                                                    (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                    (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
depthClampEnable)))
  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" mkVkCmdSetPolygonModeEXT
  :: FunPtr (Ptr CommandBuffer_T -> PolygonMode -> IO ()) -> Ptr CommandBuffer_T -> PolygonMode -> IO ()

-- | vkCmdSetPolygonModeEXT - Specify polygon mode dynamically for a command
-- buffer
--
-- = Description
--
-- This command sets the polygon mode for subsequent drawing commands when
-- the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_POLYGON_MODE_EXT' set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo'::@polygonMode@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetPolygonModeEXT-extendedDynamicState3PolygonMode-07422#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3PolygonMode extendedDynamicState3PolygonMode>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetPolygonModeEXT-fillModeNonSolid-07424# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-fillModeNonSolid fillModeNonSolid>
--     feature is not enabled, @polygonMode@ /must/ be
--     'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_FILL' or
--     'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_FILL_RECTANGLE_NV'
--
-- -   #VUID-vkCmdSetPolygonModeEXT-polygonMode-07425# If the
--     @VK_NV_fill_rectangle@ extension is not enabled, @polygonMode@
--     /must/ not be
--     'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_FILL_RECTANGLE_NV'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetPolygonModeEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetPolygonModeEXT-polygonMode-parameter# @polygonMode@
--     /must/ be a valid 'Vulkan.Core10.Enums.PolygonMode.PolygonMode'
--     value
--
-- -   #VUID-vkCmdSetPolygonModeEXT-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-vkCmdSetPolygonModeEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetPolygonModeEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.PolygonMode.PolygonMode'
cmdSetPolygonModeEXT :: forall io
                      . (MonadIO io)
                     => -- | @commandBuffer@ is the command buffer into which the command will be
                        -- recorded.
                        CommandBuffer
                     -> -- | @polygonMode@ specifies polygon mode.
                        PolygonMode
                     -> io ()
cmdSetPolygonModeEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> PolygonMode -> io ()
cmdSetPolygonModeEXT CommandBuffer
commandBuffer PolygonMode
polygonMode = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetPolygonModeEXTPtr :: FunPtr (Ptr CommandBuffer_T -> PolygonMode -> IO ())
vkCmdSetPolygonModeEXTPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> PolygonMode -> IO ())
pVkCmdSetPolygonModeEXT (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 -> PolygonMode -> IO ())
vkCmdSetPolygonModeEXTPtr 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 vkCmdSetPolygonModeEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetPolygonModeEXT' :: Ptr CommandBuffer_T -> PolygonMode -> IO ()
vkCmdSetPolygonModeEXT' = FunPtr (Ptr CommandBuffer_T -> PolygonMode -> IO ())
-> Ptr CommandBuffer_T -> PolygonMode -> IO ()
mkVkCmdSetPolygonModeEXT FunPtr (Ptr CommandBuffer_T -> PolygonMode -> IO ())
vkCmdSetPolygonModeEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetPolygonModeEXT" (Ptr CommandBuffer_T -> PolygonMode -> IO ()
vkCmdSetPolygonModeEXT'
                                               (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                               (PolygonMode
polygonMode))
  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" mkVkCmdSetRasterizationSamplesEXT
  :: FunPtr (Ptr CommandBuffer_T -> SampleCountFlagBits -> IO ()) -> Ptr CommandBuffer_T -> SampleCountFlagBits -> IO ()

-- | vkCmdSetRasterizationSamplesEXT - Specify the rasterization samples
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the @rasterizationSamples@ for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@rasterizationSamples@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetRasterizationSamplesEXT-extendedDynamicState3RasterizationSamples-07414#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3RasterizationSamples extendedDynamicState3RasterizationSamples>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetRasterizationSamplesEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetRasterizationSamplesEXT-rasterizationSamples-parameter#
--     @rasterizationSamples@ /must/ be a valid
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' value
--
-- -   #VUID-vkCmdSetRasterizationSamplesEXT-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-vkCmdSetRasterizationSamplesEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetRasterizationSamplesEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits'
cmdSetRasterizationSamplesEXT :: forall io
                               . (MonadIO io)
                              => -- | @commandBuffer@ is the command buffer into which the command will be
                                 -- recorded.
                                 CommandBuffer
                              -> -- | @rasterizationSamples@ specifies @rasterizationSamples@.
                                 ("rasterizationSamples" ::: SampleCountFlagBits)
                              -> io ()
cmdSetRasterizationSamplesEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("rasterizationSamples" ::: SampleCountFlagBits) -> io ()
cmdSetRasterizationSamplesEXT CommandBuffer
commandBuffer "rasterizationSamples" ::: SampleCountFlagBits
rasterizationSamples = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetRasterizationSamplesEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("rasterizationSamples" ::: SampleCountFlagBits) -> IO ())
vkCmdSetRasterizationSamplesEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("rasterizationSamples" ::: SampleCountFlagBits) -> IO ())
pVkCmdSetRasterizationSamplesEXT (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
   -> ("rasterizationSamples" ::: SampleCountFlagBits) -> IO ())
vkCmdSetRasterizationSamplesEXTPtr 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 vkCmdSetRasterizationSamplesEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetRasterizationSamplesEXT' :: Ptr CommandBuffer_T
-> ("rasterizationSamples" ::: SampleCountFlagBits) -> IO ()
vkCmdSetRasterizationSamplesEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("rasterizationSamples" ::: SampleCountFlagBits) -> IO ())
-> Ptr CommandBuffer_T
-> ("rasterizationSamples" ::: SampleCountFlagBits)
-> IO ()
mkVkCmdSetRasterizationSamplesEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("rasterizationSamples" ::: SampleCountFlagBits) -> IO ())
vkCmdSetRasterizationSamplesEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetRasterizationSamplesEXT" (Ptr CommandBuffer_T
-> ("rasterizationSamples" ::: SampleCountFlagBits) -> IO ()
vkCmdSetRasterizationSamplesEXT'
                                                        (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                        ("rasterizationSamples" ::: SampleCountFlagBits
rasterizationSamples))
  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" mkVkCmdSetSampleMaskEXT
  :: FunPtr (Ptr CommandBuffer_T -> SampleCountFlagBits -> Ptr SampleMask -> IO ()) -> Ptr CommandBuffer_T -> SampleCountFlagBits -> Ptr SampleMask -> IO ()

-- | vkCmdSetSampleMaskEXT - Specify the sample mask dynamically for a
-- command buffer
--
-- = Description
--
-- This command sets the sample mask for subsequent drawing commands when
-- the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT' set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@pSampleMask@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetSampleMaskEXT-extendedDynamicState3SampleMask-07342#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3SampleMask extendedDynamicState3SampleMask>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetSampleMaskEXT-commandBuffer-parameter# @commandBuffer@
--     /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetSampleMaskEXT-samples-parameter# @samples@ /must/ be a
--     valid 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits'
--     value
--
-- -   #VUID-vkCmdSetSampleMaskEXT-pSampleMask-parameter# @pSampleMask@
--     /must/ be a valid pointer to an array of
--     \(\lceil{\mathit{samples} \over 32}\rceil\)
--     'Vulkan.Core10.FundamentalTypes.SampleMask' values
--
-- -   #VUID-vkCmdSetSampleMaskEXT-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-vkCmdSetSampleMaskEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetSampleMaskEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits',
-- 'Vulkan.Core10.FundamentalTypes.SampleMask'
cmdSetSampleMaskEXT :: forall io
                     . (MonadIO io)
                    => -- | @commandBuffer@ is the command buffer into which the command will be
                       -- recorded.
                       CommandBuffer
                    -> -- | @samples@ specifies the number of sample bits in the @pSampleMask@.
                       ("samples" ::: SampleCountFlagBits)
                    -> -- | @pSampleMask@ is a pointer to an array of VkSampleMask values, where the
                       -- array size is based on the @samples@ parameter.
                       ("sampleMask" ::: Vector SampleMask)
                    -> io ()
cmdSetSampleMaskEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("rasterizationSamples" ::: SampleCountFlagBits)
-> ("sampleMask" ::: Vector SampleMask)
-> io ()
cmdSetSampleMaskEXT CommandBuffer
commandBuffer "rasterizationSamples" ::: SampleCountFlagBits
samples "sampleMask" ::: Vector SampleMask
sampleMask = 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 vkCmdSetSampleMaskEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("rasterizationSamples" ::: SampleCountFlagBits)
   -> ("pSampleMask" ::: Ptr SampleMask)
   -> IO ())
vkCmdSetSampleMaskEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("rasterizationSamples" ::: SampleCountFlagBits)
      -> ("pSampleMask" ::: Ptr SampleMask)
      -> IO ())
pVkCmdSetSampleMaskEXT (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
   -> ("rasterizationSamples" ::: SampleCountFlagBits)
   -> ("pSampleMask" ::: Ptr SampleMask)
   -> IO ())
vkCmdSetSampleMaskEXTPtr 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 vkCmdSetSampleMaskEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetSampleMaskEXT' :: Ptr CommandBuffer_T
-> ("rasterizationSamples" ::: SampleCountFlagBits)
-> ("pSampleMask" ::: Ptr SampleMask)
-> IO ()
vkCmdSetSampleMaskEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("rasterizationSamples" ::: SampleCountFlagBits)
   -> ("pSampleMask" ::: Ptr SampleMask)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("rasterizationSamples" ::: SampleCountFlagBits)
-> ("pSampleMask" ::: Ptr SampleMask)
-> IO ()
mkVkCmdSetSampleMaskEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("rasterizationSamples" ::: SampleCountFlagBits)
   -> ("pSampleMask" ::: Ptr SampleMask)
   -> IO ())
vkCmdSetSampleMaskEXTPtr
  "pSampleMask" ::: Ptr SampleMask
pPSampleMask <- 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 @SampleMask ((forall a. Vector a -> Int
Data.Vector.length ("sampleMask" ::: Vector SampleMask
sampleMask)) forall a. Num a => a -> a -> a
* Int
4)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i SampleMask
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pSampleMask" ::: Ptr SampleMask
pPSampleMask forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SampleMask) (SampleMask
e)) ("sampleMask" ::: Vector SampleMask
sampleMask)
  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
"vkCmdSetSampleMaskEXT" (Ptr CommandBuffer_T
-> ("rasterizationSamples" ::: SampleCountFlagBits)
-> ("pSampleMask" ::: Ptr SampleMask)
-> IO ()
vkCmdSetSampleMaskEXT'
                                                     (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                     ("rasterizationSamples" ::: SampleCountFlagBits
samples)
                                                     ("pSampleMask" ::: Ptr SampleMask
pPSampleMask))
  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" mkVkCmdSetAlphaToCoverageEnableEXT
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetAlphaToCoverageEnableEXT - Specify the alpha to coverage enable
-- state dynamically for a command buffer
--
-- = Description
--
-- This command sets the @alphaToCoverageEnable@ state for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@alphaToCoverageEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetAlphaToCoverageEnableEXT-extendedDynamicState3AlphaToCoverageEnable-07343#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3AlphaToCoverageEnable extendedDynamicState3AlphaToCoverageEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetAlphaToCoverageEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetAlphaToCoverageEnableEXT-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-vkCmdSetAlphaToCoverageEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetAlphaToCoverageEnableEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetAlphaToCoverageEnableEXT :: forall io
                                . (MonadIO io)
                               => -- | @commandBuffer@ is the command buffer into which the command will be
                                  -- recorded.
                                  CommandBuffer
                               -> -- | @alphaToCoverageEnable@ specifies the @alphaToCoverageEnable@ state.
                                  ("alphaToCoverageEnable" ::: Bool)
                               -> io ()
cmdSetAlphaToCoverageEnableEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetAlphaToCoverageEnableEXT CommandBuffer
commandBuffer Bool
alphaToCoverageEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetAlphaToCoverageEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetAlphaToCoverageEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetAlphaToCoverageEnableEXT (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetAlphaToCoverageEnableEXTPtr 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 vkCmdSetAlphaToCoverageEnableEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetAlphaToCoverageEnableEXT' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetAlphaToCoverageEnableEXT' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetAlphaToCoverageEnableEXT FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetAlphaToCoverageEnableEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetAlphaToCoverageEnableEXT" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetAlphaToCoverageEnableEXT'
                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                         (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
alphaToCoverageEnable)))
  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" mkVkCmdSetAlphaToOneEnableEXT
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetAlphaToOneEnableEXT - Specify the alpha to one enable state
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the @alphaToOneEnable@ state for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_ONE_ENABLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineMultisampleStateCreateInfo'::@alphaToOneEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetAlphaToOneEnableEXT-extendedDynamicState3AlphaToOneEnable-07345#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3AlphaToOneEnable extendedDynamicState3AlphaToOneEnable>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetAlphaToOneEnableEXT-alphaToOne-07607# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-alphaToOne alphaToOne>
--     feature is not enabled, @alphaToOneEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetAlphaToOneEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetAlphaToOneEnableEXT-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-vkCmdSetAlphaToOneEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetAlphaToOneEnableEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetAlphaToOneEnableEXT :: forall io
                           . (MonadIO io)
                          => -- | @commandBuffer@ is the command buffer into which the command will be
                             -- recorded.
                             CommandBuffer
                          -> -- | @alphaToOneEnable@ specifies the @alphaToOneEnable@ state.
                             ("alphaToOneEnable" ::: Bool)
                          -> io ()
cmdSetAlphaToOneEnableEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetAlphaToOneEnableEXT CommandBuffer
commandBuffer Bool
alphaToOneEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetAlphaToOneEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetAlphaToOneEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetAlphaToOneEnableEXT (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetAlphaToOneEnableEXTPtr 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 vkCmdSetAlphaToOneEnableEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetAlphaToOneEnableEXT' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetAlphaToOneEnableEXT' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetAlphaToOneEnableEXT FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetAlphaToOneEnableEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetAlphaToOneEnableEXT" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetAlphaToOneEnableEXT'
                                                    (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                    (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
alphaToOneEnable)))
  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" mkVkCmdSetLogicOpEnableEXT
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetLogicOpEnableEXT - Specify dynamically whether logical
-- operations are enabled for a command buffer
--
-- = Description
--
-- This command sets whether logical operations are enabled for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_ENABLE_EXT' set
-- in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendStateCreateInfo'::@logicOpEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetLogicOpEnableEXT-extendedDynamicState3LogicOpEnable-07365#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3LogicOpEnable extendedDynamicState3LogicOpEnable>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetLogicOpEnableEXT-logicOp-07366# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-logicOp logicOp>
--     feature is not enabled, @logicOpEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetLogicOpEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetLogicOpEnableEXT-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-vkCmdSetLogicOpEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetLogicOpEnableEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetLogicOpEnableEXT :: forall io
                        . (MonadIO io)
                       => -- | @commandBuffer@ is the command buffer into which the command will be
                          -- recorded.
                          CommandBuffer
                       -> -- | @logicOpEnable@ specifies whether logical operations are enabled.
                          ("logicOpEnable" ::: Bool)
                       -> io ()
cmdSetLogicOpEnableEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetLogicOpEnableEXT CommandBuffer
commandBuffer Bool
logicOpEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetLogicOpEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetLogicOpEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetLogicOpEnableEXT (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetLogicOpEnableEXTPtr 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 vkCmdSetLogicOpEnableEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetLogicOpEnableEXT' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetLogicOpEnableEXT' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetLogicOpEnableEXT FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetLogicOpEnableEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetLogicOpEnableEXT" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetLogicOpEnableEXT'
                                                 (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                 (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
logicOpEnable)))
  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" mkVkCmdSetColorBlendEnableEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr Bool32 -> IO ()

-- | vkCmdSetColorBlendEnableEXT - Specify the @blendEnable@ for each
-- attachment dynamically for a command buffer
--
-- = Description
--
-- This command sets the color blending enable of the specified color
-- attachments for subsequent drawing commands when the graphics pipeline
-- is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'::@blendEnable@
-- values used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetColorBlendEnableEXT-extendedDynamicState3ColorBlendEnable-07355#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ColorBlendEnable extendedDynamicState3ColorBlendEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetColorBlendEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetColorBlendEnableEXT-pColorBlendEnables-parameter#
--     @pColorBlendEnables@ /must/ be a valid pointer to an array of
--     @attachmentCount@ 'Vulkan.Core10.FundamentalTypes.Bool32' values
--
-- -   #VUID-vkCmdSetColorBlendEnableEXT-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-vkCmdSetColorBlendEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetColorBlendEnableEXT-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- -   #VUID-vkCmdSetColorBlendEnableEXT-attachmentCount-arraylength#
--     @attachmentCount@ /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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetColorBlendEnableEXT :: forall io
                           . (MonadIO io)
                          => -- | @commandBuffer@ is the command buffer into which the command will be
                             -- recorded.
                             CommandBuffer
                          -> -- | @firstAttachment@ the first color attachment the color blending enable
                             -- applies.
                             ("firstAttachment" ::: Word32)
                          -> -- | @pColorBlendEnables@ an array of booleans to indicate whether color
                             -- blending is enabled for the corresponding attachment.
                             ("colorBlendEnables" ::: Vector Bool)
                          -> io ()
cmdSetColorBlendEnableEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> SampleMask -> ("colorBlendEnables" ::: Vector Bool) -> io ()
cmdSetColorBlendEnableEXT CommandBuffer
commandBuffer
                            SampleMask
firstAttachment
                            "colorBlendEnables" ::: Vector Bool
colorBlendEnables = 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 vkCmdSetColorBlendEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32))
   -> IO ())
vkCmdSetColorBlendEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> SampleMask
      -> SampleMask
      -> ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32))
      -> IO ())
pVkCmdSetColorBlendEnableEXT (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
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32))
   -> IO ())
vkCmdSetColorBlendEnableEXTPtr 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 vkCmdSetColorBlendEnableEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetColorBlendEnableEXT' :: Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32))
-> IO ()
vkCmdSetColorBlendEnableEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32))
   -> IO ())
-> Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32))
-> IO ()
mkVkCmdSetColorBlendEnableEXT FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32))
   -> IO ())
vkCmdSetColorBlendEnableEXTPtr
  "pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32)
pPColorBlendEnables <- 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 @Bool32 ((forall a. Vector a -> Int
Data.Vector.length ("colorBlendEnables" ::: Vector Bool
colorBlendEnables)) forall a. Num a => a -> a -> a
* Int
4)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Bool
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32)
pPColorBlendEnables forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
e))) ("colorBlendEnables" ::: Vector Bool
colorBlendEnables)
  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
"vkCmdSetColorBlendEnableEXT" (Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32))
-> IO ()
vkCmdSetColorBlendEnableEXT'
                                                           (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                           (SampleMask
firstAttachment)
                                                           ((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
$ ("colorBlendEnables" ::: Vector Bool
colorBlendEnables)) :: Word32))
                                                           ("pColorBlendEnables" ::: Ptr ("depthClampEnable" ::: Bool32)
pPColorBlendEnables))
  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" mkVkCmdSetColorBlendEquationEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ColorBlendEquationEXT -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ColorBlendEquationEXT -> IO ()

-- | vkCmdSetColorBlendEquationEXT - Specify the blend factors and operations
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the color blending factors and operations of the
-- specified attachments for subsequent drawing commands when the graphics
-- pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'::@srcColorBlendFactor@,
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'::@dstColorBlendFactor@,
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'::@colorBlendOp@,
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'::@srcAlphaBlendFactor@,
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'::@dstAlphaBlendFactor@,
-- and
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'::@alphaBlendOp@
-- values used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetColorBlendEquationEXT-extendedDynamicState3ColorBlendEquation-07356#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ColorBlendEquation extendedDynamicState3ColorBlendEquation>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetColorBlendEquationEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetColorBlendEquationEXT-pColorBlendEquations-parameter#
--     @pColorBlendEquations@ /must/ be a valid pointer to an array of
--     @attachmentCount@ valid 'ColorBlendEquationEXT' structures
--
-- -   #VUID-vkCmdSetColorBlendEquationEXT-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-vkCmdSetColorBlendEquationEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetColorBlendEquationEXT-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- -   #VUID-vkCmdSetColorBlendEquationEXT-attachmentCount-arraylength#
--     @attachmentCount@ /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_state3 VK_EXT_extended_dynamic_state3>,
-- 'ColorBlendEquationEXT', 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetColorBlendEquationEXT :: forall io
                             . (MonadIO io)
                            => -- | @commandBuffer@ is the command buffer into which the command will be
                               -- recorded.
                               CommandBuffer
                            -> -- | @firstAttachment@ the first color attachment the color blend factors and
                               -- operations apply to.
                               ("firstAttachment" ::: Word32)
                            -> -- | @pColorBlendEquations@ an array of 'ColorBlendEquationEXT' structs that
                               -- specify the color blend factors and operations for the corresponding
                               -- attachments.
                               ("colorBlendEquations" ::: Vector ColorBlendEquationEXT)
                            -> io ()
cmdSetColorBlendEquationEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> SampleMask
-> ("colorBlendEquations" ::: Vector ColorBlendEquationEXT)
-> io ()
cmdSetColorBlendEquationEXT CommandBuffer
commandBuffer
                              SampleMask
firstAttachment
                              "colorBlendEquations" ::: Vector ColorBlendEquationEXT
colorBlendEquations = 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 vkCmdSetColorBlendEquationEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
   -> IO ())
vkCmdSetColorBlendEquationEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> SampleMask
      -> SampleMask
      -> ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
      -> IO ())
pVkCmdSetColorBlendEquationEXT (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
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
   -> IO ())
vkCmdSetColorBlendEquationEXTPtr 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 vkCmdSetColorBlendEquationEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetColorBlendEquationEXT' :: Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
-> IO ()
vkCmdSetColorBlendEquationEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
   -> IO ())
-> Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
-> IO ()
mkVkCmdSetColorBlendEquationEXT FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
   -> IO ())
vkCmdSetColorBlendEquationEXTPtr
  "pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
pPColorBlendEquations <- 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 @ColorBlendEquationEXT ((forall a. Vector a -> Int
Data.Vector.length ("colorBlendEquations" ::: Vector ColorBlendEquationEXT
colorBlendEquations)) 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 ColorBlendEquationEXT
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
pPColorBlendEquations forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
24 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ColorBlendEquationEXT) (ColorBlendEquationEXT
e)) ("colorBlendEquations" ::: Vector ColorBlendEquationEXT
colorBlendEquations)
  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
"vkCmdSetColorBlendEquationEXT" (Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
-> IO ()
vkCmdSetColorBlendEquationEXT'
                                                             (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                             (SampleMask
firstAttachment)
                                                             ((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
$ ("colorBlendEquations" ::: Vector ColorBlendEquationEXT
colorBlendEquations)) :: Word32))
                                                             ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
pPColorBlendEquations))
  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" mkVkCmdSetColorWriteMaskEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ColorComponentFlags -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ColorComponentFlags -> IO ()

-- | vkCmdSetColorWriteMaskEXT - Specify the color write masks for each
-- attachment dynamically for a command buffer
--
-- = Description
--
-- This command sets the color write masks of the specified attachments for
-- subsequent drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Core10.Pipeline.PipelineColorBlendAttachmentState'::@colorWriteMask@
-- values used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetColorWriteMaskEXT-extendedDynamicState3ColorWriteMask-07364#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ColorWriteMask extendedDynamicState3ColorWriteMask>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetColorWriteMaskEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetColorWriteMaskEXT-pColorWriteMasks-parameter#
--     @pColorWriteMasks@ /must/ be a valid pointer to an array of
--     @attachmentCount@ valid combinations of
--     'Vulkan.Core10.Enums.ColorComponentFlagBits.ColorComponentFlagBits'
--     values
--
-- -   #VUID-vkCmdSetColorWriteMaskEXT-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-vkCmdSetColorWriteMaskEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetColorWriteMaskEXT-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- -   #VUID-vkCmdSetColorWriteMaskEXT-attachmentCount-arraylength#
--     @attachmentCount@ /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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Enums.ColorComponentFlagBits.ColorComponentFlags',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetColorWriteMaskEXT :: forall io
                         . (MonadIO io)
                        => -- | @commandBuffer@ is the command buffer into which the command will be
                           -- recorded.
                           CommandBuffer
                        -> -- | @firstAttachment@ the first color attachment the color write masks apply
                           -- to.
                           ("firstAttachment" ::: Word32)
                        -> -- | @pColorWriteMasks@ an array of
                           -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.ColorComponentFlags' values
                           -- that specify the color write masks of the corresponding attachments.
                           ("colorWriteMasks" ::: Vector ColorComponentFlags)
                        -> io ()
cmdSetColorWriteMaskEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> SampleMask
-> ("colorWriteMasks" ::: Vector ColorComponentFlags)
-> io ()
cmdSetColorWriteMaskEXT CommandBuffer
commandBuffer
                          SampleMask
firstAttachment
                          "colorWriteMasks" ::: Vector ColorComponentFlags
colorWriteMasks = 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 vkCmdSetColorWriteMaskEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorWriteMasks" ::: Ptr ColorComponentFlags)
   -> IO ())
vkCmdSetColorWriteMaskEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> SampleMask
      -> SampleMask
      -> ("pColorWriteMasks" ::: Ptr ColorComponentFlags)
      -> IO ())
pVkCmdSetColorWriteMaskEXT (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
   -> SampleMask
   -> SampleMask
   -> ("pColorWriteMasks" ::: Ptr ColorComponentFlags)
   -> IO ())
vkCmdSetColorWriteMaskEXTPtr 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 vkCmdSetColorWriteMaskEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetColorWriteMaskEXT' :: Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorWriteMasks" ::: Ptr ColorComponentFlags)
-> IO ()
vkCmdSetColorWriteMaskEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorWriteMasks" ::: Ptr ColorComponentFlags)
   -> IO ())
-> Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorWriteMasks" ::: Ptr ColorComponentFlags)
-> IO ()
mkVkCmdSetColorWriteMaskEXT FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorWriteMasks" ::: Ptr ColorComponentFlags)
   -> IO ())
vkCmdSetColorWriteMaskEXTPtr
  "pColorWriteMasks" ::: Ptr ColorComponentFlags
pPColorWriteMasks <- 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 @ColorComponentFlags ((forall a. Vector a -> Int
Data.Vector.length ("colorWriteMasks" ::: Vector ColorComponentFlags
colorWriteMasks)) forall a. Num a => a -> a -> a
* Int
4)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i ColorComponentFlags
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorWriteMasks" ::: Ptr ColorComponentFlags
pPColorWriteMasks forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ColorComponentFlags) (ColorComponentFlags
e)) ("colorWriteMasks" ::: Vector ColorComponentFlags
colorWriteMasks)
  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
"vkCmdSetColorWriteMaskEXT" (Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorWriteMasks" ::: Ptr ColorComponentFlags)
-> IO ()
vkCmdSetColorWriteMaskEXT'
                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                         (SampleMask
firstAttachment)
                                                         ((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
$ ("colorWriteMasks" ::: Vector ColorComponentFlags
colorWriteMasks)) :: Word32))
                                                         ("pColorWriteMasks" ::: Ptr ColorComponentFlags
pPColorWriteMasks))
  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" mkVkCmdSetRasterizationStreamEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> IO ()

-- | vkCmdSetRasterizationStreamEXT - Specify the rasterization stream
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the @rasterizationStream@ state for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.PipelineRasterizationStateStreamCreateInfoEXT'::@rasterizationStream@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetRasterizationStreamEXT-extendedDynamicState3RasterizationStream-07410#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3RasterizationStream extendedDynamicState3RasterizationStream>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetRasterizationStreamEXT-transformFeedback-07411# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-transformFeedback transformFeedback>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetRasterizationStreamEXT-rasterizationStream-07412#
--     @rasterizationStream@ /must/ be less than
--     'Vulkan.Extensions.VK_EXT_transform_feedback.PhysicalDeviceTransformFeedbackPropertiesEXT'::@maxTransformFeedbackStreams@
--
-- -   #VUID-vkCmdSetRasterizationStreamEXT-rasterizationStream-07413#
--     @rasterizationStream@ /must/ be zero if
--     'Vulkan.Extensions.VK_EXT_transform_feedback.PhysicalDeviceTransformFeedbackPropertiesEXT'::@transformFeedbackRasterizationStreamSelect@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetRasterizationStreamEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetRasterizationStreamEXT-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-vkCmdSetRasterizationStreamEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetRasterizationStreamEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetRasterizationStreamEXT :: forall io
                              . (MonadIO io)
                             => -- | @commandBuffer@ is the command buffer into which the command will be
                                -- recorded.
                                CommandBuffer
                             -> -- | @rasterizationStream@ specifies the @rasterizationStream@ state.
                                ("rasterizationStream" ::: Word32)
                             -> io ()
cmdSetRasterizationStreamEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> SampleMask -> io ()
cmdSetRasterizationStreamEXT CommandBuffer
commandBuffer SampleMask
rasterizationStream = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetRasterizationStreamEXTPtr :: FunPtr (Ptr CommandBuffer_T -> SampleMask -> IO ())
vkCmdSetRasterizationStreamEXTPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> SampleMask -> IO ())
pVkCmdSetRasterizationStreamEXT (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 -> SampleMask -> IO ())
vkCmdSetRasterizationStreamEXTPtr 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 vkCmdSetRasterizationStreamEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetRasterizationStreamEXT' :: Ptr CommandBuffer_T -> SampleMask -> IO ()
vkCmdSetRasterizationStreamEXT' = FunPtr (Ptr CommandBuffer_T -> SampleMask -> IO ())
-> Ptr CommandBuffer_T -> SampleMask -> IO ()
mkVkCmdSetRasterizationStreamEXT FunPtr (Ptr CommandBuffer_T -> SampleMask -> IO ())
vkCmdSetRasterizationStreamEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetRasterizationStreamEXT" (Ptr CommandBuffer_T -> SampleMask -> IO ()
vkCmdSetRasterizationStreamEXT'
                                                       (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                       (SampleMask
rasterizationStream))
  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" mkVkCmdSetConservativeRasterizationModeEXT
  :: FunPtr (Ptr CommandBuffer_T -> ConservativeRasterizationModeEXT -> IO ()) -> Ptr CommandBuffer_T -> ConservativeRasterizationModeEXT -> IO ()

-- | vkCmdSetConservativeRasterizationModeEXT - Specify the conservative
-- rasterization mode dynamically for a command buffer
--
-- = Description
--
-- This command sets the @conservativeRasterizationMode@ state for
-- subsequent drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.PipelineRasterizationConservativeStateCreateInfoEXT'::@conservativeRasterizationMode@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetConservativeRasterizationModeEXT-extendedDynamicState3ConservativeRasterizationMode-07426#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ConservativeRasterizationMode extendedDynamicState3ConservativeRasterizationMode>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetConservativeRasterizationModeEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetConservativeRasterizationModeEXT-conservativeRasterizationMode-parameter#
--     @conservativeRasterizationMode@ /must/ be a valid
--     'Vulkan.Extensions.VK_EXT_conservative_rasterization.ConservativeRasterizationModeEXT'
--     value
--
-- -   #VUID-vkCmdSetConservativeRasterizationModeEXT-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-vkCmdSetConservativeRasterizationModeEXT-commandBuffer-cmdpool#
--     The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetConservativeRasterizationModeEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.ConservativeRasterizationModeEXT'
cmdSetConservativeRasterizationModeEXT :: forall io
                                        . (MonadIO io)
                                       => -- | @commandBuffer@ is the command buffer into which the command will be
                                          -- recorded.
                                          CommandBuffer
                                       -> -- | @conservativeRasterizationMode@ specifies the
                                          -- @conservativeRasterizationMode@ state.
                                          ConservativeRasterizationModeEXT
                                       -> io ()
cmdSetConservativeRasterizationModeEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> ConservativeRasterizationModeEXT -> io ()
cmdSetConservativeRasterizationModeEXT CommandBuffer
commandBuffer
                                         ConservativeRasterizationModeEXT
conservativeRasterizationMode = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetConservativeRasterizationModeEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> ConservativeRasterizationModeEXT -> IO ())
vkCmdSetConservativeRasterizationModeEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ConservativeRasterizationModeEXT -> IO ())
pVkCmdSetConservativeRasterizationModeEXT (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 -> ConservativeRasterizationModeEXT -> IO ())
vkCmdSetConservativeRasterizationModeEXTPtr 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 vkCmdSetConservativeRasterizationModeEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetConservativeRasterizationModeEXT' :: Ptr CommandBuffer_T -> ConservativeRasterizationModeEXT -> IO ()
vkCmdSetConservativeRasterizationModeEXT' = FunPtr
  (Ptr CommandBuffer_T -> ConservativeRasterizationModeEXT -> IO ())
-> Ptr CommandBuffer_T -> ConservativeRasterizationModeEXT -> IO ()
mkVkCmdSetConservativeRasterizationModeEXT FunPtr
  (Ptr CommandBuffer_T -> ConservativeRasterizationModeEXT -> IO ())
vkCmdSetConservativeRasterizationModeEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetConservativeRasterizationModeEXT" (Ptr CommandBuffer_T -> ConservativeRasterizationModeEXT -> IO ()
vkCmdSetConservativeRasterizationModeEXT'
                                                                 (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                                 (ConservativeRasterizationModeEXT
conservativeRasterizationMode))
  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" mkVkCmdSetExtraPrimitiveOverestimationSizeEXT
  :: FunPtr (Ptr CommandBuffer_T -> CFloat -> IO ()) -> Ptr CommandBuffer_T -> CFloat -> IO ()

-- | vkCmdSetExtraPrimitiveOverestimationSizeEXT - Specify the conservative
-- rasterization extra primitive overestimation size dynamically for a
-- command buffer
--
-- = Description
--
-- This command sets the @extraPrimitiveOverestimationSize@ for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXTRA_PRIMITIVE_OVERESTIMATION_SIZE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_conservative_rasterization.PipelineRasterizationConservativeStateCreateInfoEXT'::@extraPrimitiveOverestimationSize@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetExtraPrimitiveOverestimationSizeEXT-extendedDynamicState3ExtraPrimitiveOverestimationSize-07427#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ExtraPrimitiveOverestimationSize extendedDynamicState3ExtraPrimitiveOverestimationSize>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetExtraPrimitiveOverestimationSizeEXT-extraPrimitiveOverestimationSize-07428#
--     @extraPrimitiveOverestimationSize@ /must/ be in the range of @0.0@
--     to
--     'Vulkan.Extensions.VK_EXT_conservative_rasterization.PhysicalDeviceConservativeRasterizationPropertiesEXT'::@maxExtraPrimitiveOverestimationSize@
--     inclusive
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetExtraPrimitiveOverestimationSizeEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetExtraPrimitiveOverestimationSizeEXT-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-vkCmdSetExtraPrimitiveOverestimationSizeEXT-commandBuffer-cmdpool#
--     The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetExtraPrimitiveOverestimationSizeEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetExtraPrimitiveOverestimationSizeEXT :: forall io
                                           . (MonadIO io)
                                          => -- | @commandBuffer@ is the command buffer into which the command will be
                                             -- recorded.
                                             CommandBuffer
                                          -> -- | @extraPrimitiveOverestimationSize@ specifies the
                                             -- @extraPrimitiveOverestimationSize@.
                                             ("extraPrimitiveOverestimationSize" ::: Float)
                                          -> io ()
cmdSetExtraPrimitiveOverestimationSizeEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("extraPrimitiveOverestimationSize" ::: Float) -> io ()
cmdSetExtraPrimitiveOverestimationSizeEXT CommandBuffer
commandBuffer
                                            "extraPrimitiveOverestimationSize" ::: Float
extraPrimitiveOverestimationSize = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetExtraPrimitiveOverestimationSizeEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("extraPrimitiveOverestimationSize" ::: CFloat) -> IO ())
vkCmdSetExtraPrimitiveOverestimationSizeEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("extraPrimitiveOverestimationSize" ::: CFloat) -> IO ())
pVkCmdSetExtraPrimitiveOverestimationSizeEXT (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
   -> ("extraPrimitiveOverestimationSize" ::: CFloat) -> IO ())
vkCmdSetExtraPrimitiveOverestimationSizeEXTPtr 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 vkCmdSetExtraPrimitiveOverestimationSizeEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetExtraPrimitiveOverestimationSizeEXT' :: Ptr CommandBuffer_T
-> ("extraPrimitiveOverestimationSize" ::: CFloat) -> IO ()
vkCmdSetExtraPrimitiveOverestimationSizeEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("extraPrimitiveOverestimationSize" ::: CFloat) -> IO ())
-> Ptr CommandBuffer_T
-> ("extraPrimitiveOverestimationSize" ::: CFloat)
-> IO ()
mkVkCmdSetExtraPrimitiveOverestimationSizeEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("extraPrimitiveOverestimationSize" ::: CFloat) -> IO ())
vkCmdSetExtraPrimitiveOverestimationSizeEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetExtraPrimitiveOverestimationSizeEXT" (Ptr CommandBuffer_T
-> ("extraPrimitiveOverestimationSize" ::: CFloat) -> IO ()
vkCmdSetExtraPrimitiveOverestimationSizeEXT'
                                                                    (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                                    (("extraPrimitiveOverestimationSize" ::: Float)
-> "extraPrimitiveOverestimationSize" ::: CFloat
CFloat ("extraPrimitiveOverestimationSize" ::: Float
extraPrimitiveOverestimationSize)))
  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" mkVkCmdSetDepthClipEnableEXT
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetDepthClipEnableEXT - Specify dynamically whether depth clipping
-- is enabled in the command buffer
--
-- = Description
--
-- This command sets whether depth clipping is enabled or disabled for
-- subsequent drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_ENABLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_depth_clip_enable.PipelineRasterizationDepthClipStateCreateInfoEXT'::@depthClipEnable@
-- value used to create the currently active pipeline, or is set to the
-- inverse of
-- 'Vulkan.Core10.Pipeline.PipelineRasterizationStateCreateInfo'::@depthClampEnable@
-- if
-- 'Vulkan.Extensions.VK_EXT_depth_clip_enable.PipelineRasterizationDepthClipStateCreateInfoEXT'
-- is not specified.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetDepthClipEnableEXT-extendedDynamicState3DepthClipEnable-07450#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3DepthClipEnable extendedDynamicState3DepthClipEnable>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetDepthClipEnableEXT-depthClipEnable-07451# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-depthClipEnable depthClipEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetDepthClipEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetDepthClipEnableEXT-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-vkCmdSetDepthClipEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetDepthClipEnableEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetDepthClipEnableEXT :: forall io
                          . (MonadIO io)
                         => -- | @commandBuffer@ is the command buffer into which the command will be
                            -- recorded.
                            CommandBuffer
                         -> -- | @depthClipEnable@ specifies whether depth clipping is enabled.
                            ("depthClipEnable" ::: Bool)
                         -> io ()
cmdSetDepthClipEnableEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetDepthClipEnableEXT CommandBuffer
commandBuffer Bool
depthClipEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetDepthClipEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetDepthClipEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetDepthClipEnableEXT (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetDepthClipEnableEXTPtr 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 vkCmdSetDepthClipEnableEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetDepthClipEnableEXT' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetDepthClipEnableEXT' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetDepthClipEnableEXT FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetDepthClipEnableEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetDepthClipEnableEXT" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetDepthClipEnableEXT'
                                                   (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                   (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
depthClipEnable)))
  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" mkVkCmdSetSampleLocationsEnableEXT
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetSampleLocationsEnableEXT - Specify the samples locations enable
-- state dynamically for a command buffer
--
-- = Description
--
-- This command sets the @sampleLocationsEnable@ state for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'::@sampleLocationsEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetSampleLocationsEnableEXT-extendedDynamicState3SampleLocationsEnable-07415#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3SampleLocationsEnable extendedDynamicState3SampleLocationsEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetSampleLocationsEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetSampleLocationsEnableEXT-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-vkCmdSetSampleLocationsEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetSampleLocationsEnableEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetSampleLocationsEnableEXT :: forall io
                                . (MonadIO io)
                               => -- | @commandBuffer@ is the command buffer into which the command will be
                                  -- recorded.
                                  CommandBuffer
                               -> -- | @sampleLocationsEnable@ specifies the @sampleLocationsEnable@ state.
                                  ("sampleLocationsEnable" ::: Bool)
                               -> io ()
cmdSetSampleLocationsEnableEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetSampleLocationsEnableEXT CommandBuffer
commandBuffer Bool
sampleLocationsEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetSampleLocationsEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetSampleLocationsEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetSampleLocationsEnableEXT (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetSampleLocationsEnableEXTPtr 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 vkCmdSetSampleLocationsEnableEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetSampleLocationsEnableEXT' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetSampleLocationsEnableEXT' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetSampleLocationsEnableEXT FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetSampleLocationsEnableEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetSampleLocationsEnableEXT" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetSampleLocationsEnableEXT'
                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                         (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
sampleLocationsEnable)))
  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" mkVkCmdSetColorBlendAdvancedEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ColorBlendAdvancedEXT -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ColorBlendAdvancedEXT -> IO ()

-- | vkCmdSetColorBlendAdvancedEXT - Specify the advanced color blend state
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the advanced blend operation parameters of the
-- specified attachments for subsequent drawing commands when the graphics
-- pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PipelineColorBlendAdvancedStateCreateInfoEXT'::@srcPremultiplied@,
-- 'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PipelineColorBlendAdvancedStateCreateInfoEXT'::@dstPremultiplied@,
-- and
-- 'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PipelineColorBlendAdvancedStateCreateInfoEXT'::@blendOverlap@
-- values used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetColorBlendAdvancedEXT-extendedDynamicState3ColorBlendAdvanced-07504#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ColorBlendAdvanced extendedDynamicState3ColorBlendAdvanced>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetColorBlendAdvancedEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetColorBlendAdvancedEXT-pColorBlendAdvanced-parameter#
--     @pColorBlendAdvanced@ /must/ be a valid pointer to an array of
--     @attachmentCount@ valid 'ColorBlendAdvancedEXT' structures
--
-- -   #VUID-vkCmdSetColorBlendAdvancedEXT-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-vkCmdSetColorBlendAdvancedEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetColorBlendAdvancedEXT-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- -   #VUID-vkCmdSetColorBlendAdvancedEXT-attachmentCount-arraylength#
--     @attachmentCount@ /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_state3 VK_EXT_extended_dynamic_state3>,
-- 'ColorBlendAdvancedEXT', 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetColorBlendAdvancedEXT :: forall io
                             . (MonadIO io)
                            => -- | @commandBuffer@ is the command buffer into which the command will be
                               -- recorded.
                               CommandBuffer
                            -> -- | @firstAttachment@ the first color attachment the advanced blend
                               -- parameters apply to.
                               ("firstAttachment" ::: Word32)
                            -> -- | @pColorBlendAdvanced@ an array of 'ColorBlendAdvancedEXT' structs that
                               -- specify the advanced color blend parameters for the corresponding
                               -- attachments.
                               ("colorBlendAdvanced" ::: Vector ColorBlendAdvancedEXT)
                            -> io ()
cmdSetColorBlendAdvancedEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> SampleMask
-> ("colorBlendAdvanced" ::: Vector ColorBlendAdvancedEXT)
-> io ()
cmdSetColorBlendAdvancedEXT CommandBuffer
commandBuffer
                              SampleMask
firstAttachment
                              "colorBlendAdvanced" ::: Vector ColorBlendAdvancedEXT
colorBlendAdvanced = 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 vkCmdSetColorBlendAdvancedEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
   -> IO ())
vkCmdSetColorBlendAdvancedEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> SampleMask
      -> SampleMask
      -> ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
      -> IO ())
pVkCmdSetColorBlendAdvancedEXT (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
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
   -> IO ())
vkCmdSetColorBlendAdvancedEXTPtr 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 vkCmdSetColorBlendAdvancedEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetColorBlendAdvancedEXT' :: Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
-> IO ()
vkCmdSetColorBlendAdvancedEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
   -> IO ())
-> Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
-> IO ()
mkVkCmdSetColorBlendAdvancedEXT FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
   -> IO ())
vkCmdSetColorBlendAdvancedEXTPtr
  "pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
pPColorBlendAdvanced <- 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 @ColorBlendAdvancedEXT ((forall a. Vector a -> Int
Data.Vector.length ("colorBlendAdvanced" ::: Vector ColorBlendAdvancedEXT
colorBlendAdvanced)) forall a. Num a => a -> a -> a
* Int
20)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i ColorBlendAdvancedEXT
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
pPColorBlendAdvanced forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
20 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ColorBlendAdvancedEXT) (ColorBlendAdvancedEXT
e)) ("colorBlendAdvanced" ::: Vector ColorBlendAdvancedEXT
colorBlendAdvanced)
  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
"vkCmdSetColorBlendAdvancedEXT" (Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
-> IO ()
vkCmdSetColorBlendAdvancedEXT'
                                                             (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                             (SampleMask
firstAttachment)
                                                             ((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
$ ("colorBlendAdvanced" ::: Vector ColorBlendAdvancedEXT
colorBlendAdvanced)) :: Word32))
                                                             ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
pPColorBlendAdvanced))
  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" mkVkCmdSetProvokingVertexModeEXT
  :: FunPtr (Ptr CommandBuffer_T -> ProvokingVertexModeEXT -> IO ()) -> Ptr CommandBuffer_T -> ProvokingVertexModeEXT -> IO ()

-- | vkCmdSetProvokingVertexModeEXT - Specify the provoking vertex mode
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the @provokingVertexMode@ state for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PROVOKING_VERTEX_MODE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_provoking_vertex.PipelineRasterizationProvokingVertexStateCreateInfoEXT'::@provokingVertexMode@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetProvokingVertexModeEXT-extendedDynamicState3ProvokingVertexMode-07446#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ProvokingVertexMode extendedDynamicState3ProvokingVertexMode>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetProvokingVertexModeEXT-provokingVertexMode-07447# If
--     @provokingVertexMode@ is
--     'Vulkan.Extensions.VK_EXT_provoking_vertex.PROVOKING_VERTEX_MODE_LAST_VERTEX_EXT',
--     then the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-provokingVertexLast provokingVertexLast>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetProvokingVertexModeEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetProvokingVertexModeEXT-provokingVertexMode-parameter#
--     @provokingVertexMode@ /must/ be a valid
--     'Vulkan.Extensions.VK_EXT_provoking_vertex.ProvokingVertexModeEXT'
--     value
--
-- -   #VUID-vkCmdSetProvokingVertexModeEXT-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-vkCmdSetProvokingVertexModeEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetProvokingVertexModeEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Extensions.VK_EXT_provoking_vertex.ProvokingVertexModeEXT'
cmdSetProvokingVertexModeEXT :: forall io
                              . (MonadIO io)
                             => -- | @commandBuffer@ is the command buffer into which the command will be
                                -- recorded.
                                CommandBuffer
                             -> -- | @provokingVertexMode@ specifies the @provokingVertexMode@ state.
                                ProvokingVertexModeEXT
                             -> io ()
cmdSetProvokingVertexModeEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> ProvokingVertexModeEXT -> io ()
cmdSetProvokingVertexModeEXT CommandBuffer
commandBuffer ProvokingVertexModeEXT
provokingVertexMode = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetProvokingVertexModeEXTPtr :: FunPtr (Ptr CommandBuffer_T -> ProvokingVertexModeEXT -> IO ())
vkCmdSetProvokingVertexModeEXTPtr = DeviceCmds
-> FunPtr (Ptr CommandBuffer_T -> ProvokingVertexModeEXT -> IO ())
pVkCmdSetProvokingVertexModeEXT (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 -> ProvokingVertexModeEXT -> IO ())
vkCmdSetProvokingVertexModeEXTPtr 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 vkCmdSetProvokingVertexModeEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetProvokingVertexModeEXT' :: Ptr CommandBuffer_T -> ProvokingVertexModeEXT -> IO ()
vkCmdSetProvokingVertexModeEXT' = FunPtr (Ptr CommandBuffer_T -> ProvokingVertexModeEXT -> IO ())
-> Ptr CommandBuffer_T -> ProvokingVertexModeEXT -> IO ()
mkVkCmdSetProvokingVertexModeEXT FunPtr (Ptr CommandBuffer_T -> ProvokingVertexModeEXT -> IO ())
vkCmdSetProvokingVertexModeEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetProvokingVertexModeEXT" (Ptr CommandBuffer_T -> ProvokingVertexModeEXT -> IO ()
vkCmdSetProvokingVertexModeEXT'
                                                       (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                       (ProvokingVertexModeEXT
provokingVertexMode))
  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" mkVkCmdSetLineRasterizationModeEXT
  :: FunPtr (Ptr CommandBuffer_T -> LineRasterizationModeEXT -> IO ()) -> Ptr CommandBuffer_T -> LineRasterizationModeEXT -> IO ()

-- | vkCmdSetLineRasterizationModeEXT - Specify the line rasterization mode
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the @lineRasterizationMode@ state for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_line_rasterization.PipelineRasterizationLineStateCreateInfoEXT'::@lineRasterizationMode@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetLineRasterizationModeEXT-extendedDynamicState3LineRasterizationMode-07417#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3LineRasterizationMode extendedDynamicState3LineRasterizationMode>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetLineRasterizationModeEXT-lineRasterizationMode-07418#
--     If @lineRasterizationMode@ is
--     'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_EXT',
--     then the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-rectangularLines rectangularLines>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetLineRasterizationModeEXT-lineRasterizationMode-07419#
--     If @lineRasterizationMode@ is
--     'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_BRESENHAM_EXT',
--     then the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-bresenhamLines bresenhamLines>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetLineRasterizationModeEXT-lineRasterizationMode-07420#
--     If @lineRasterizationMode@ is
--     'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT',
--     then the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-smoothLines smoothLines>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetLineRasterizationModeEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetLineRasterizationModeEXT-lineRasterizationMode-parameter#
--     @lineRasterizationMode@ /must/ be a valid
--     'Vulkan.Extensions.VK_EXT_line_rasterization.LineRasterizationModeEXT'
--     value
--
-- -   #VUID-vkCmdSetLineRasterizationModeEXT-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-vkCmdSetLineRasterizationModeEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetLineRasterizationModeEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Extensions.VK_EXT_line_rasterization.LineRasterizationModeEXT'
cmdSetLineRasterizationModeEXT :: forall io
                                . (MonadIO io)
                               => -- | @commandBuffer@ is the command buffer into which the command will be
                                  -- recorded.
                                  CommandBuffer
                               -> -- | @lineRasterizationMode@ specifies the @lineRasterizationMode@ state.
                                  LineRasterizationModeEXT
                               -> io ()
cmdSetLineRasterizationModeEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> LineRasterizationModeEXT -> io ()
cmdSetLineRasterizationModeEXT CommandBuffer
commandBuffer LineRasterizationModeEXT
lineRasterizationMode = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetLineRasterizationModeEXTPtr :: FunPtr (Ptr CommandBuffer_T -> LineRasterizationModeEXT -> IO ())
vkCmdSetLineRasterizationModeEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> LineRasterizationModeEXT -> IO ())
pVkCmdSetLineRasterizationModeEXT (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 -> LineRasterizationModeEXT -> IO ())
vkCmdSetLineRasterizationModeEXTPtr 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 vkCmdSetLineRasterizationModeEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetLineRasterizationModeEXT' :: Ptr CommandBuffer_T -> LineRasterizationModeEXT -> IO ()
vkCmdSetLineRasterizationModeEXT' = FunPtr (Ptr CommandBuffer_T -> LineRasterizationModeEXT -> IO ())
-> Ptr CommandBuffer_T -> LineRasterizationModeEXT -> IO ()
mkVkCmdSetLineRasterizationModeEXT FunPtr (Ptr CommandBuffer_T -> LineRasterizationModeEXT -> IO ())
vkCmdSetLineRasterizationModeEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetLineRasterizationModeEXT" (Ptr CommandBuffer_T -> LineRasterizationModeEXT -> IO ()
vkCmdSetLineRasterizationModeEXT'
                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                         (LineRasterizationModeEXT
lineRasterizationMode))
  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" mkVkCmdSetLineStippleEnableEXT
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetLineStippleEnableEXT - Specify the line stipple enable
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the @stippledLineEnable@ state for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_line_rasterization.PipelineRasterizationLineStateCreateInfoEXT'::@stippledLineEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetLineStippleEnableEXT-extendedDynamicState3LineStippleEnable-07421#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3LineStippleEnable extendedDynamicState3LineStippleEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetLineStippleEnableEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetLineStippleEnableEXT-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-vkCmdSetLineStippleEnableEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetLineStippleEnableEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetLineStippleEnableEXT :: forall io
                            . (MonadIO io)
                           => -- | @commandBuffer@ is the command buffer into which the command will be
                              -- recorded.
                              CommandBuffer
                           -> -- | @stippledLineEnable@ specifies the @stippledLineEnable@ state.
                              ("stippledLineEnable" ::: Bool)
                           -> io ()
cmdSetLineStippleEnableEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetLineStippleEnableEXT CommandBuffer
commandBuffer Bool
stippledLineEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetLineStippleEnableEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetLineStippleEnableEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetLineStippleEnableEXT (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetLineStippleEnableEXTPtr 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 vkCmdSetLineStippleEnableEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetLineStippleEnableEXT' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetLineStippleEnableEXT' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetLineStippleEnableEXT FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetLineStippleEnableEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetLineStippleEnableEXT" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetLineStippleEnableEXT'
                                                     (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                     (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
stippledLineEnable)))
  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" mkVkCmdSetDepthClipNegativeOneToOneEXT
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetDepthClipNegativeOneToOneEXT - Specify the negative one to one
-- depth clip mode dynamically for a command buffer
--
-- = Description
--
-- This command sets the @negativeOneToOne@ state for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_NEGATIVE_ONE_TO_ONE_EXT'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_EXT_depth_clip_control.PipelineViewportDepthClipControlCreateInfoEXT'::@negativeOneToOne@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetDepthClipNegativeOneToOneEXT-extendedDynamicState3DepthClipNegativeOneToOne-07452#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3DepthClipNegativeOneToOne extendedDynamicState3DepthClipNegativeOneToOne>
--     feature /must/ be enabled
--
-- -   #VUID-vkCmdSetDepthClipNegativeOneToOneEXT-depthClipControl-07453#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-depthClipControl depthClipControl>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetDepthClipNegativeOneToOneEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetDepthClipNegativeOneToOneEXT-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-vkCmdSetDepthClipNegativeOneToOneEXT-commandBuffer-cmdpool#
--     The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetDepthClipNegativeOneToOneEXT-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetDepthClipNegativeOneToOneEXT :: forall io
                                    . (MonadIO io)
                                   => -- | @commandBuffer@ is the command buffer into which the command will be
                                      -- recorded.
                                      CommandBuffer
                                   -> -- | @negativeOneToOne@ specifies the @negativeOneToOne@ state.
                                      ("negativeOneToOne" ::: Bool)
                                   -> io ()
cmdSetDepthClipNegativeOneToOneEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetDepthClipNegativeOneToOneEXT CommandBuffer
commandBuffer Bool
negativeOneToOne = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetDepthClipNegativeOneToOneEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetDepthClipNegativeOneToOneEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetDepthClipNegativeOneToOneEXT (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetDepthClipNegativeOneToOneEXTPtr 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 vkCmdSetDepthClipNegativeOneToOneEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetDepthClipNegativeOneToOneEXT' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetDepthClipNegativeOneToOneEXT' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetDepthClipNegativeOneToOneEXT FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetDepthClipNegativeOneToOneEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetDepthClipNegativeOneToOneEXT" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetDepthClipNegativeOneToOneEXT'
                                                             (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                             (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
negativeOneToOne)))
  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" mkVkCmdSetViewportWScalingEnableNV
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetViewportWScalingEnableNV - Specify the viewport W scaling enable
-- state dynamically for a command buffer
--
-- = Description
--
-- This command sets the @viewportWScalingEnable@ state for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_ENABLE_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportWScalingEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetViewportWScalingEnableNV-extendedDynamicState3ViewportWScalingEnable-07580#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ViewportWScalingEnable extendedDynamicState3ViewportWScalingEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetViewportWScalingEnableNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetViewportWScalingEnableNV-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-vkCmdSetViewportWScalingEnableNV-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetViewportWScalingEnableNV-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetViewportWScalingEnableNV :: forall io
                                . (MonadIO io)
                               => -- | @commandBuffer@ is the command buffer into which the command will be
                                  -- recorded.
                                  CommandBuffer
                               -> -- | @viewportWScalingEnable@ specifies the @viewportWScalingEnable@ state.
                                  ("viewportWScalingEnable" ::: Bool)
                               -> io ()
cmdSetViewportWScalingEnableNV :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetViewportWScalingEnableNV CommandBuffer
commandBuffer
                                 Bool
viewportWScalingEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetViewportWScalingEnableNVPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetViewportWScalingEnableNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetViewportWScalingEnableNV (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetViewportWScalingEnableNVPtr 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 vkCmdSetViewportWScalingEnableNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetViewportWScalingEnableNV' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetViewportWScalingEnableNV' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetViewportWScalingEnableNV FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetViewportWScalingEnableNVPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetViewportWScalingEnableNV" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetViewportWScalingEnableNV'
                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                         (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
viewportWScalingEnable)))
  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" mkVkCmdSetViewportSwizzleNV
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ViewportSwizzleNV -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Ptr ViewportSwizzleNV -> IO ()

-- | vkCmdSetViewportSwizzleNV - Specify the viewport swizzle state
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the viewport swizzle state for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV' set
-- in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@viewportCount@,
-- and
-- 'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV'::@pViewportSwizzles@
-- values used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetViewportSwizzleNV-extendedDynamicState3ViewportSwizzle-07445#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ViewportSwizzle extendedDynamicState3ViewportSwizzle>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetViewportSwizzleNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetViewportSwizzleNV-pViewportSwizzles-parameter#
--     @pViewportSwizzles@ /must/ be a valid pointer to an array of
--     @viewportCount@ valid
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.ViewportSwizzleNV'
--     structures
--
-- -   #VUID-vkCmdSetViewportSwizzleNV-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-vkCmdSetViewportSwizzleNV-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetViewportSwizzleNV-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- -   #VUID-vkCmdSetViewportSwizzleNV-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Extensions.VK_NV_viewport_swizzle.ViewportSwizzleNV'
cmdSetViewportSwizzleNV :: forall io
                         . (MonadIO io)
                        => -- | @commandBuffer@ is the command buffer into which the command will be
                           -- recorded.
                           CommandBuffer
                        -> -- | @firstViewport@ is the index of the first viewport whose parameters are
                           -- updated by the command.
                           ("firstViewport" ::: Word32)
                        -> -- | @pViewportSwizzles@ is a pointer to an array of
                           -- 'Vulkan.Extensions.VK_NV_viewport_swizzle.ViewportSwizzleNV' structures
                           -- specifying viewport swizzles.
                           ("viewportSwizzles" ::: Vector ViewportSwizzleNV)
                        -> io ()
cmdSetViewportSwizzleNV :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> SampleMask
-> ("viewportSwizzles" ::: Vector ViewportSwizzleNV)
-> io ()
cmdSetViewportSwizzleNV CommandBuffer
commandBuffer
                          SampleMask
firstViewport
                          "viewportSwizzles" ::: Vector ViewportSwizzleNV
viewportSwizzles = 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 vkCmdSetViewportSwizzleNVPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV)
   -> IO ())
vkCmdSetViewportSwizzleNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> SampleMask
      -> SampleMask
      -> ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV)
      -> IO ())
pVkCmdSetViewportSwizzleNV (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
   -> SampleMask
   -> SampleMask
   -> ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV)
   -> IO ())
vkCmdSetViewportSwizzleNVPtr 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 vkCmdSetViewportSwizzleNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetViewportSwizzleNV' :: Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV)
-> IO ()
vkCmdSetViewportSwizzleNV' = FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV)
   -> IO ())
-> Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV)
-> IO ()
mkVkCmdSetViewportSwizzleNV FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> SampleMask
   -> ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV)
   -> IO ())
vkCmdSetViewportSwizzleNVPtr
  "pViewportSwizzles" ::: Ptr ViewportSwizzleNV
pPViewportSwizzles <- 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 @ViewportSwizzleNV ((forall a. Vector a -> Int
Data.Vector.length ("viewportSwizzles" ::: Vector ViewportSwizzleNV
viewportSwizzles)) 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 ViewportSwizzleNV
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV
pPViewportSwizzles forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
16 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr ViewportSwizzleNV) (ViewportSwizzleNV
e)) ("viewportSwizzles" ::: Vector ViewportSwizzleNV
viewportSwizzles)
  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
"vkCmdSetViewportSwizzleNV" (Ptr CommandBuffer_T
-> SampleMask
-> SampleMask
-> ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV)
-> IO ()
vkCmdSetViewportSwizzleNV'
                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                         (SampleMask
firstViewport)
                                                         ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ ("viewportSwizzles" ::: Vector ViewportSwizzleNV
viewportSwizzles)) :: Word32))
                                                         ("pViewportSwizzles" ::: Ptr ViewportSwizzleNV
pPViewportSwizzles))
  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" mkVkCmdSetCoverageToColorEnableNV
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetCoverageToColorEnableNV - Specify the coverage to color enable
-- state dynamically for a command buffer
--
-- = Description
--
-- This command sets the @coverageToColorEnable@ state for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_fragment_coverage_to_color.PipelineCoverageToColorStateCreateInfoNV'::@coverageToColorEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetCoverageToColorEnableNV-extendedDynamicState3CoverageToColorEnable-07347#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3CoverageToColorEnable extendedDynamicState3CoverageToColorEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetCoverageToColorEnableNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetCoverageToColorEnableNV-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-vkCmdSetCoverageToColorEnableNV-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetCoverageToColorEnableNV-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetCoverageToColorEnableNV :: forall io
                               . (MonadIO io)
                              => -- | @commandBuffer@ is the command buffer into which the command will be
                                 -- recorded.
                                 CommandBuffer
                              -> -- | @coverageToColorEnable@ specifies the @coverageToColorEnable@ state.
                                 ("coverageToColorEnable" ::: Bool)
                              -> io ()
cmdSetCoverageToColorEnableNV :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetCoverageToColorEnableNV CommandBuffer
commandBuffer Bool
coverageToColorEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetCoverageToColorEnableNVPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetCoverageToColorEnableNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetCoverageToColorEnableNV (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetCoverageToColorEnableNVPtr 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 vkCmdSetCoverageToColorEnableNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetCoverageToColorEnableNV' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetCoverageToColorEnableNV' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetCoverageToColorEnableNV FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetCoverageToColorEnableNVPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetCoverageToColorEnableNV" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetCoverageToColorEnableNV'
                                                        (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                        (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
coverageToColorEnable)))
  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" mkVkCmdSetCoverageToColorLocationNV
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> IO ()

-- | vkCmdSetCoverageToColorLocationNV - Specify the coverage to color
-- location dynamically for a command buffer
--
-- = Description
--
-- This command sets the @coverageToColorLocation@ state for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_LOCATION_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_fragment_coverage_to_color.PipelineCoverageToColorStateCreateInfoNV'::@coverageToColorLocation@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetCoverageToColorLocationNV-extendedDynamicState3CoverageToColorLocation-07348#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3CoverageToColorLocation extendedDynamicState3CoverageToColorLocation>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetCoverageToColorLocationNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetCoverageToColorLocationNV-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-vkCmdSetCoverageToColorLocationNV-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetCoverageToColorLocationNV-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetCoverageToColorLocationNV :: forall io
                                 . (MonadIO io)
                                => -- | @commandBuffer@ is the command buffer into which the command will be
                                   -- recorded.
                                   CommandBuffer
                                -> -- | @coverageToColorLocation@ specifies the @coverageToColorLocation@ state.
                                   ("coverageToColorLocation" ::: Word32)
                                -> io ()
cmdSetCoverageToColorLocationNV :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> SampleMask -> io ()
cmdSetCoverageToColorLocationNV CommandBuffer
commandBuffer
                                  SampleMask
coverageToColorLocation = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetCoverageToColorLocationNVPtr :: FunPtr (Ptr CommandBuffer_T -> SampleMask -> IO ())
vkCmdSetCoverageToColorLocationNVPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> SampleMask -> IO ())
pVkCmdSetCoverageToColorLocationNV (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 -> SampleMask -> IO ())
vkCmdSetCoverageToColorLocationNVPtr 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 vkCmdSetCoverageToColorLocationNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetCoverageToColorLocationNV' :: Ptr CommandBuffer_T -> SampleMask -> IO ()
vkCmdSetCoverageToColorLocationNV' = FunPtr (Ptr CommandBuffer_T -> SampleMask -> IO ())
-> Ptr CommandBuffer_T -> SampleMask -> IO ()
mkVkCmdSetCoverageToColorLocationNV FunPtr (Ptr CommandBuffer_T -> SampleMask -> IO ())
vkCmdSetCoverageToColorLocationNVPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetCoverageToColorLocationNV" (Ptr CommandBuffer_T -> SampleMask -> IO ()
vkCmdSetCoverageToColorLocationNV'
                                                          (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                          (SampleMask
coverageToColorLocation))
  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" mkVkCmdSetCoverageModulationModeNV
  :: FunPtr (Ptr CommandBuffer_T -> CoverageModulationModeNV -> IO ()) -> Ptr CommandBuffer_T -> CoverageModulationModeNV -> IO ()

-- | vkCmdSetCoverageModulationModeNV - Specify the coverage modulation mode
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the @coverageModulationMode@ state for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_MODE_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.PipelineCoverageModulationStateCreateInfoNV'::@coverageModulationMode@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetCoverageModulationModeNV-extendedDynamicState3CoverageModulationMode-07350#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3CoverageModulationMode extendedDynamicState3CoverageModulationMode>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetCoverageModulationModeNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetCoverageModulationModeNV-coverageModulationMode-parameter#
--     @coverageModulationMode@ /must/ be a valid
--     'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.CoverageModulationModeNV'
--     value
--
-- -   #VUID-vkCmdSetCoverageModulationModeNV-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-vkCmdSetCoverageModulationModeNV-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetCoverageModulationModeNV-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.CoverageModulationModeNV'
cmdSetCoverageModulationModeNV :: forall io
                                . (MonadIO io)
                               => -- | @commandBuffer@ is the command buffer into which the command will be
                                  -- recorded.
                                  CommandBuffer
                               -> -- | @coverageModulationMode@ specifies the @coverageModulationMode@ state.
                                  CoverageModulationModeNV
                               -> io ()
cmdSetCoverageModulationModeNV :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> CoverageModulationModeNV -> io ()
cmdSetCoverageModulationModeNV CommandBuffer
commandBuffer
                                 CoverageModulationModeNV
coverageModulationMode = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetCoverageModulationModeNVPtr :: FunPtr (Ptr CommandBuffer_T -> CoverageModulationModeNV -> IO ())
vkCmdSetCoverageModulationModeNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> CoverageModulationModeNV -> IO ())
pVkCmdSetCoverageModulationModeNV (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 -> CoverageModulationModeNV -> IO ())
vkCmdSetCoverageModulationModeNVPtr 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 vkCmdSetCoverageModulationModeNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetCoverageModulationModeNV' :: Ptr CommandBuffer_T -> CoverageModulationModeNV -> IO ()
vkCmdSetCoverageModulationModeNV' = FunPtr (Ptr CommandBuffer_T -> CoverageModulationModeNV -> IO ())
-> Ptr CommandBuffer_T -> CoverageModulationModeNV -> IO ()
mkVkCmdSetCoverageModulationModeNV FunPtr (Ptr CommandBuffer_T -> CoverageModulationModeNV -> IO ())
vkCmdSetCoverageModulationModeNVPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetCoverageModulationModeNV" (Ptr CommandBuffer_T -> CoverageModulationModeNV -> IO ()
vkCmdSetCoverageModulationModeNV'
                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                         (CoverageModulationModeNV
coverageModulationMode))
  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" mkVkCmdSetCoverageModulationTableEnableNV
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetCoverageModulationTableEnableNV - Specify the coverage
-- modulation table enable state dynamically for a command buffer
--
-- = Description
--
-- This command sets the @coverageModulationTableEnable@ state for
-- subsequent drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.PipelineCoverageModulationStateCreateInfoNV'::@coverageModulationTableEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetCoverageModulationTableEnableNV-extendedDynamicState3CoverageModulationTableEnable-07351#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3CoverageModulationTableEnable extendedDynamicState3CoverageModulationTableEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetCoverageModulationTableEnableNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetCoverageModulationTableEnableNV-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-vkCmdSetCoverageModulationTableEnableNV-commandBuffer-cmdpool#
--     The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetCoverageModulationTableEnableNV-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetCoverageModulationTableEnableNV :: forall io
                                       . (MonadIO io)
                                      => -- | @commandBuffer@ is the command buffer into which the command will be
                                         -- recorded.
                                         CommandBuffer
                                      -> -- | @coverageModulationTableEnable@ specifies the
                                         -- @coverageModulationTableEnable@ state.
                                         ("coverageModulationTableEnable" ::: Bool)
                                      -> io ()
cmdSetCoverageModulationTableEnableNV :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetCoverageModulationTableEnableNV CommandBuffer
commandBuffer
                                        Bool
coverageModulationTableEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetCoverageModulationTableEnableNVPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetCoverageModulationTableEnableNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetCoverageModulationTableEnableNV (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetCoverageModulationTableEnableNVPtr 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 vkCmdSetCoverageModulationTableEnableNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetCoverageModulationTableEnableNV' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetCoverageModulationTableEnableNV' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetCoverageModulationTableEnableNV FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetCoverageModulationTableEnableNVPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetCoverageModulationTableEnableNV" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetCoverageModulationTableEnableNV'
                                                                (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                                (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
coverageModulationTableEnable)))
  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" mkVkCmdSetCoverageModulationTableNV
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr CFloat -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr CFloat -> IO ()

-- | vkCmdSetCoverageModulationTableNV - Specify the coverage modulation
-- table dynamically for a command buffer
--
-- = Description
--
-- This command sets the table of modulation factors for subsequent drawing
-- commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.PipelineCoverageModulationStateCreateInfoNV'::@coverageModulationTableCount@,
-- and
-- 'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.PipelineCoverageModulationStateCreateInfoNV'::@pCoverageModulationTable@
-- values used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetCoverageModulationTableNV-extendedDynamicState3CoverageModulationTable-07352#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3CoverageModulationTable extendedDynamicState3CoverageModulationTable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetCoverageModulationTableNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetCoverageModulationTableNV-pCoverageModulationTable-parameter#
--     @pCoverageModulationTable@ /must/ be a valid pointer to an array of
--     @coverageModulationTableCount@ @float@ values
--
-- -   #VUID-vkCmdSetCoverageModulationTableNV-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-vkCmdSetCoverageModulationTableNV-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetCoverageModulationTableNV-videocoding# This command
--     /must/ only be called outside of a video coding scope
--
-- -   #VUID-vkCmdSetCoverageModulationTableNV-coverageModulationTableCount-arraylength#
--     @coverageModulationTableCount@ /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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetCoverageModulationTableNV :: forall io
                                 . (MonadIO io)
                                => -- | @commandBuffer@ is the command buffer into which the command will be
                                   -- recorded.
                                   CommandBuffer
                                -> -- | @pCoverageModulationTable@ specifies the table of modulation factors
                                   -- containing a value for each number of covered samples.
                                   ("coverageModulationTable" ::: Vector Float)
                                -> io ()
cmdSetCoverageModulationTableNV :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("coverageModulationTable"
    ::: Vector ("extraPrimitiveOverestimationSize" ::: Float))
-> io ()
cmdSetCoverageModulationTableNV CommandBuffer
commandBuffer
                                  "coverageModulationTable"
::: Vector ("extraPrimitiveOverestimationSize" ::: Float)
coverageModulationTable = 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 vkCmdSetCoverageModulationTableNVPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> ("pCoverageModulationTable"
       ::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat))
   -> IO ())
vkCmdSetCoverageModulationTableNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> SampleMask
      -> ("pCoverageModulationTable"
          ::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat))
      -> IO ())
pVkCmdSetCoverageModulationTableNV (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
   -> SampleMask
   -> ("pCoverageModulationTable"
       ::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat))
   -> IO ())
vkCmdSetCoverageModulationTableNVPtr 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 vkCmdSetCoverageModulationTableNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetCoverageModulationTableNV' :: Ptr CommandBuffer_T
-> SampleMask
-> ("pCoverageModulationTable"
    ::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat))
-> IO ()
vkCmdSetCoverageModulationTableNV' = FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> ("pCoverageModulationTable"
       ::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat))
   -> IO ())
-> Ptr CommandBuffer_T
-> SampleMask
-> ("pCoverageModulationTable"
    ::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat))
-> IO ()
mkVkCmdSetCoverageModulationTableNV FunPtr
  (Ptr CommandBuffer_T
   -> SampleMask
   -> ("pCoverageModulationTable"
       ::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat))
   -> IO ())
vkCmdSetCoverageModulationTableNVPtr
  "pCoverageModulationTable"
::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat)
pPCoverageModulationTable <- 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 @CFloat ((forall a. Vector a -> Int
Data.Vector.length ("coverageModulationTable"
::: Vector ("extraPrimitiveOverestimationSize" ::: Float)
coverageModulationTable)) forall a. Num a => a -> a -> a
* Int
4)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i "extraPrimitiveOverestimationSize" ::: Float
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pCoverageModulationTable"
::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat)
pPCoverageModulationTable forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
4 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr CFloat) (("extraPrimitiveOverestimationSize" ::: Float)
-> "extraPrimitiveOverestimationSize" ::: CFloat
CFloat ("extraPrimitiveOverestimationSize" ::: Float
e))) ("coverageModulationTable"
::: Vector ("extraPrimitiveOverestimationSize" ::: Float)
coverageModulationTable)
  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
"vkCmdSetCoverageModulationTableNV" (Ptr CommandBuffer_T
-> SampleMask
-> ("pCoverageModulationTable"
    ::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat))
-> IO ()
vkCmdSetCoverageModulationTableNV'
                                                                 (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
$ ("coverageModulationTable"
::: Vector ("extraPrimitiveOverestimationSize" ::: Float)
coverageModulationTable)) :: Word32))
                                                                 ("pCoverageModulationTable"
::: Ptr ("extraPrimitiveOverestimationSize" ::: CFloat)
pPCoverageModulationTable))
  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" mkVkCmdSetShadingRateImageEnableNV
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetShadingRateImageEnableNV - Specify the shading rate image enable
-- state dynamically for a command buffer
--
-- = Description
--
-- This command sets the @shadingRateImageEnable@ state for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SHADING_RATE_IMAGE_ENABLE_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'::@shadingRateImageEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetShadingRateImageEnableNV-extendedDynamicState3ShadingRateImageEnable-07416#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3ShadingRateImageEnable extendedDynamicState3ShadingRateImageEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetShadingRateImageEnableNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetShadingRateImageEnableNV-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-vkCmdSetShadingRateImageEnableNV-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetShadingRateImageEnableNV-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetShadingRateImageEnableNV :: forall io
                                . (MonadIO io)
                               => -- | @commandBuffer@ is the command buffer into which the command will be
                                  -- recorded.
                                  CommandBuffer
                               -> -- | @shadingRateImageEnable@ specifies the @shadingRateImageEnable@ state.
                                  ("shadingRateImageEnable" ::: Bool)
                               -> io ()
cmdSetShadingRateImageEnableNV :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetShadingRateImageEnableNV CommandBuffer
commandBuffer
                                 Bool
shadingRateImageEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetShadingRateImageEnableNVPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetShadingRateImageEnableNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetShadingRateImageEnableNV (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetShadingRateImageEnableNVPtr 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 vkCmdSetShadingRateImageEnableNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetShadingRateImageEnableNV' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetShadingRateImageEnableNV' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetShadingRateImageEnableNV FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetShadingRateImageEnableNVPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetShadingRateImageEnableNV" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetShadingRateImageEnableNV'
                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                         (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
shadingRateImageEnable)))
  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" mkVkCmdSetCoverageReductionModeNV
  :: FunPtr (Ptr CommandBuffer_T -> CoverageReductionModeNV -> IO ()) -> Ptr CommandBuffer_T -> CoverageReductionModeNV -> IO ()

-- | vkCmdSetCoverageReductionModeNV - Specify the coverage reduction mode
-- dynamically for a command buffer
--
-- = Description
--
-- This command sets the @coverageReductionMode@ state for subsequent
-- drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_REDUCTION_MODE_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_coverage_reduction_mode.PipelineCoverageReductionStateCreateInfoNV'::@coverageReductionMode@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetCoverageReductionModeNV-extendedDynamicState3CoverageReductionMode-07349#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3CoverageReductionMode extendedDynamicState3CoverageReductionMode>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetCoverageReductionModeNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetCoverageReductionModeNV-coverageReductionMode-parameter#
--     @coverageReductionMode@ /must/ be a valid
--     'Vulkan.Extensions.VK_NV_coverage_reduction_mode.CoverageReductionModeNV'
--     value
--
-- -   #VUID-vkCmdSetCoverageReductionModeNV-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-vkCmdSetCoverageReductionModeNV-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetCoverageReductionModeNV-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Extensions.VK_NV_coverage_reduction_mode.CoverageReductionModeNV'
cmdSetCoverageReductionModeNV :: forall io
                               . (MonadIO io)
                              => -- | @commandBuffer@ is the command buffer into which the command will be
                                 -- recorded.
                                 CommandBuffer
                              -> -- | @coverageReductionMode@ specifies the @coverageReductionMode@ state.
                                 CoverageReductionModeNV
                              -> io ()
cmdSetCoverageReductionModeNV :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> CoverageReductionModeNV -> io ()
cmdSetCoverageReductionModeNV CommandBuffer
commandBuffer CoverageReductionModeNV
coverageReductionMode = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetCoverageReductionModeNVPtr :: FunPtr (Ptr CommandBuffer_T -> CoverageReductionModeNV -> IO ())
vkCmdSetCoverageReductionModeNVPtr = DeviceCmds
-> FunPtr (Ptr CommandBuffer_T -> CoverageReductionModeNV -> IO ())
pVkCmdSetCoverageReductionModeNV (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 -> CoverageReductionModeNV -> IO ())
vkCmdSetCoverageReductionModeNVPtr 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 vkCmdSetCoverageReductionModeNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetCoverageReductionModeNV' :: Ptr CommandBuffer_T -> CoverageReductionModeNV -> IO ()
vkCmdSetCoverageReductionModeNV' = FunPtr (Ptr CommandBuffer_T -> CoverageReductionModeNV -> IO ())
-> Ptr CommandBuffer_T -> CoverageReductionModeNV -> IO ()
mkVkCmdSetCoverageReductionModeNV FunPtr (Ptr CommandBuffer_T -> CoverageReductionModeNV -> IO ())
vkCmdSetCoverageReductionModeNVPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetCoverageReductionModeNV" (Ptr CommandBuffer_T -> CoverageReductionModeNV -> IO ()
vkCmdSetCoverageReductionModeNV'
                                                        (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                        (CoverageReductionModeNV
coverageReductionMode))
  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" mkVkCmdSetRepresentativeFragmentTestEnableNV
  :: FunPtr (Ptr CommandBuffer_T -> Bool32 -> IO ()) -> Ptr CommandBuffer_T -> Bool32 -> IO ()

-- | vkCmdSetRepresentativeFragmentTestEnableNV - Specify the representative
-- fragment test enable dynamically for a command buffer
--
-- = Description
--
-- This command sets the @representativeFragmentTestEnable@ state for
-- subsequent drawing commands when the graphics pipeline is created with
-- 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_REPRESENTATIVE_FRAGMENT_TEST_ENABLE_NV'
-- set in
-- 'Vulkan.Core10.Pipeline.PipelineDynamicStateCreateInfo'::@pDynamicStates@.
-- Otherwise, this state is specified by the
-- 'Vulkan.Extensions.VK_NV_representative_fragment_test.PipelineRepresentativeFragmentTestStateCreateInfoNV'::@representativeFragmentTestEnable@
-- value used to create the currently active pipeline.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetRepresentativeFragmentTestEnableNV-extendedDynamicState3RepresentativeFragmentTestEnable-07346#
--     The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-extendedDynamicState3RepresentativeFragmentTestEnable extendedDynamicState3RepresentativeFragmentTestEnable>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetRepresentativeFragmentTestEnableNV-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetRepresentativeFragmentTestEnableNV-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-vkCmdSetRepresentativeFragmentTestEnableNV-commandBuffer-cmdpool#
--     The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   #VUID-vkCmdSetRepresentativeFragmentTestEnableNV-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_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdSetRepresentativeFragmentTestEnableNV :: forall io
                                          . (MonadIO io)
                                         => -- | @commandBuffer@ is the command buffer into which the command will be
                                            -- recorded.
                                            CommandBuffer
                                         -> -- | @representativeFragmentTestEnable@ specifies the
                                            -- @representativeFragmentTestEnable@ state.
                                            ("representativeFragmentTestEnable" ::: Bool)
                                         -> io ()
cmdSetRepresentativeFragmentTestEnableNV :: forall (io :: * -> *). MonadIO io => CommandBuffer -> Bool -> io ()
cmdSetRepresentativeFragmentTestEnableNV CommandBuffer
commandBuffer
                                           Bool
representativeFragmentTestEnable = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdSetRepresentativeFragmentTestEnableNVPtr :: FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetRepresentativeFragmentTestEnableNVPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
pVkCmdSetRepresentativeFragmentTestEnableNV (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 -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetRepresentativeFragmentTestEnableNVPtr 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 vkCmdSetRepresentativeFragmentTestEnableNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetRepresentativeFragmentTestEnableNV' :: Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetRepresentativeFragmentTestEnableNV' = FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
-> Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
mkVkCmdSetRepresentativeFragmentTestEnableNV FunPtr
  (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ())
vkCmdSetRepresentativeFragmentTestEnableNVPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdSetRepresentativeFragmentTestEnableNV" (Ptr CommandBuffer_T -> ("depthClampEnable" ::: Bool32) -> IO ()
vkCmdSetRepresentativeFragmentTestEnableNV'
                                                                   (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                                   (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
representativeFragmentTestEnable)))
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()


-- | VkPhysicalDeviceExtendedDynamicState3FeaturesEXT - Structure describing
-- what extended dynamic state is supported by the implementation
--
-- = Members
--
-- This structure describes the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceExtendedDynamicState3FeaturesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceExtendedDynamicState3FeaturesEXT' /can/ also
-- be used in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo'
-- to selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceExtendedDynamicState3FeaturesEXT = PhysicalDeviceExtendedDynamicState3FeaturesEXT
  { -- | #features-extendedDynamicState3TessellationDomainOrigin#
    -- @extendedDynamicState3TessellationDomainOrigin@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_TESSELLATION_DOMAIN_ORIGIN_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3TessellationDomainOrigin :: Bool
  , -- | #features-extendedDynamicState3DepthClampEnable#
    -- @extendedDynamicState3DepthClampEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLAMP_ENABLE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3DepthClampEnable :: Bool
  , -- | #features-extendedDynamicState3PolygonMode#
    -- @extendedDynamicState3PolygonMode@ indicates that the implementation
    -- supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_POLYGON_MODE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3PolygonMode :: Bool
  , -- | #features-extendedDynamicState3RasterizationSamples#
    -- @extendedDynamicState3RasterizationSamples@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_SAMPLES_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3RasterizationSamples :: Bool
  , -- | #features-extendedDynamicState3SampleMask#
    -- @extendedDynamicState3SampleMask@ indicates that the implementation
    -- supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_MASK_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3SampleMask :: Bool
  , -- | #features-extendedDynamicState3AlphaToCoverageEnable#
    -- @extendedDynamicState3AlphaToCoverageEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_COVERAGE_ENABLE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3AlphaToCoverageEnable :: Bool
  , -- | #features-extendedDynamicState3AlphaToOneEnable#
    -- @extendedDynamicState3AlphaToOneEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_ALPHA_TO_ONE_ENABLE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3AlphaToOneEnable :: Bool
  , -- | #features-extendedDynamicState3LogicOpEnable#
    -- @extendedDynamicState3LogicOpEnable@ indicates that the implementation
    -- supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LOGIC_OP_ENABLE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3LogicOpEnable :: Bool
  , -- | #features-extendedDynamicState3ColorBlendEnable#
    -- @extendedDynamicState3ColorBlendEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ENABLE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ColorBlendEnable :: Bool
  , -- | #features-extendedDynamicState3ColorBlendEquation#
    -- @extendedDynamicState3ColorBlendEquation@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_EQUATION_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ColorBlendEquation :: Bool
  , -- | #features-extendedDynamicState3ColorWriteMask#
    -- @extendedDynamicState3ColorWriteMask@ indicates that the implementation
    -- supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_WRITE_MASK_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ColorWriteMask :: Bool
  , -- | #features-extendedDynamicState3RasterizationStream#
    -- @extendedDynamicState3RasterizationStream@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_RASTERIZATION_STREAM_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3RasterizationStream :: Bool
  , -- | #features-extendedDynamicState3ConservativeRasterizationMode#
    -- @extendedDynamicState3ConservativeRasterizationMode@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CONSERVATIVE_RASTERIZATION_MODE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ConservativeRasterizationMode :: Bool
  , -- | #features-extendedDynamicState3ExtraPrimitiveOverestimationSize#
    -- @extendedDynamicState3ExtraPrimitiveOverestimationSize@ indicates that
    -- the implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXTRA_PRIMITIVE_OVERESTIMATION_SIZE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ExtraPrimitiveOverestimationSize :: Bool
  , -- | #features-extendedDynamicState3DepthClipEnable#
    -- @extendedDynamicState3DepthClipEnable@ indicates that the implementation
    -- supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_ENABLE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3DepthClipEnable :: Bool
  , -- | #features-extendedDynamicState3SampleLocationsEnable#
    -- @extendedDynamicState3SampleLocationsEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_ENABLE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3SampleLocationsEnable :: Bool
  , -- | #features-extendedDynamicState3ColorBlendAdvanced#
    -- @extendedDynamicState3ColorBlendAdvanced@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COLOR_BLEND_ADVANCED_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ColorBlendAdvanced :: Bool
  , -- | #features-extendedDynamicState3ProvokingVertexMode#
    -- @extendedDynamicState3ProvokingVertexMode@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PROVOKING_VERTEX_MODE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ProvokingVertexMode :: Bool
  , -- | #features-extendedDynamicState3LineRasterizationMode#
    -- @extendedDynamicState3LineRasterizationMode@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_RASTERIZATION_MODE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3LineRasterizationMode :: Bool
  , -- | #features-extendedDynamicState3LineStippleEnable#
    -- @extendedDynamicState3LineStippleEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_ENABLE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3LineStippleEnable :: Bool
  , -- | #features-extendedDynamicState3DepthClipNegativeOneToOne#
    -- @extendedDynamicState3DepthClipNegativeOneToOne@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_CLIP_NEGATIVE_ONE_TO_ONE_EXT'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3DepthClipNegativeOneToOne :: Bool
  , -- | #features-extendedDynamicState3ViewportWScalingEnable#
    -- @extendedDynamicState3ViewportWScalingEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_ENABLE_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ViewportWScalingEnable :: Bool
  , -- | #features-extendedDynamicState3ViewportSwizzle#
    -- @extendedDynamicState3ViewportSwizzle@ indicates that the implementation
    -- supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SWIZZLE_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ViewportSwizzle :: Bool
  , -- | #features-extendedDynamicState3CoverageToColorEnable#
    -- @extendedDynamicState3CoverageToColorEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_ENABLE_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3CoverageToColorEnable :: Bool
  , -- | #features-extendedDynamicState3CoverageToColorLocation#
    -- @extendedDynamicState3CoverageToColorLocation@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_TO_COLOR_LOCATION_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3CoverageToColorLocation :: Bool
  , -- | #features-extendedDynamicState3CoverageModulationMode#
    -- @extendedDynamicState3CoverageModulationMode@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_MODE_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3CoverageModulationMode :: Bool
  , -- | #features-extendedDynamicState3CoverageModulationTableEnable#
    -- @extendedDynamicState3CoverageModulationTableEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_ENABLE_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3CoverageModulationTableEnable :: Bool
  , -- | #features-extendedDynamicState3CoverageModulationTable#
    -- @extendedDynamicState3CoverageModulationTable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_MODULATION_TABLE_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3CoverageModulationTable :: Bool
  , -- | #features-extendedDynamicState3CoverageReductionMode#
    -- @extendedDynamicState3CoverageReductionMode@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_COVERAGE_REDUCTION_MODE_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3CoverageReductionMode :: Bool
  , -- | #features-extendedDynamicState3RepresentativeFragmentTestEnable#
    -- @extendedDynamicState3RepresentativeFragmentTestEnable@ indicates that
    -- the implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_REPRESENTATIVE_FRAGMENT_TEST_ENABLE_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3RepresentativeFragmentTestEnable :: Bool
  , -- | #features-extendedDynamicState3ShadingRateImageEnable#
    -- @extendedDynamicState3ShadingRateImageEnable@ indicates that the
    -- implementation supports the following dynamic state:
    --
    -- -   'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SHADING_RATE_IMAGE_ENABLE_NV'
    PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
extendedDynamicState3ShadingRateImageEnable :: Bool
  }
  deriving (Typeable, PhysicalDeviceExtendedDynamicState3FeaturesEXT
-> PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceExtendedDynamicState3FeaturesEXT
-> PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$c/= :: PhysicalDeviceExtendedDynamicState3FeaturesEXT
-> PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
== :: PhysicalDeviceExtendedDynamicState3FeaturesEXT
-> PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$c== :: PhysicalDeviceExtendedDynamicState3FeaturesEXT
-> PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceExtendedDynamicState3FeaturesEXT)
#endif
deriving instance Show PhysicalDeviceExtendedDynamicState3FeaturesEXT

instance ToCStruct PhysicalDeviceExtendedDynamicState3FeaturesEXT where
  withCStruct :: forall b.
PhysicalDeviceExtendedDynamicState3FeaturesEXT
-> (Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceExtendedDynamicState3FeaturesEXT
x Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
144 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p PhysicalDeviceExtendedDynamicState3FeaturesEXT
x (Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT -> IO b
f Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
-> PhysicalDeviceExtendedDynamicState3FeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p PhysicalDeviceExtendedDynamicState3FeaturesEXT{Bool
extendedDynamicState3ShadingRateImageEnable :: Bool
extendedDynamicState3RepresentativeFragmentTestEnable :: Bool
extendedDynamicState3CoverageReductionMode :: Bool
extendedDynamicState3CoverageModulationTable :: Bool
extendedDynamicState3CoverageModulationTableEnable :: Bool
extendedDynamicState3CoverageModulationMode :: Bool
extendedDynamicState3CoverageToColorLocation :: Bool
extendedDynamicState3CoverageToColorEnable :: Bool
extendedDynamicState3ViewportSwizzle :: Bool
extendedDynamicState3ViewportWScalingEnable :: Bool
extendedDynamicState3DepthClipNegativeOneToOne :: Bool
extendedDynamicState3LineStippleEnable :: Bool
extendedDynamicState3LineRasterizationMode :: Bool
extendedDynamicState3ProvokingVertexMode :: Bool
extendedDynamicState3ColorBlendAdvanced :: Bool
extendedDynamicState3SampleLocationsEnable :: Bool
extendedDynamicState3DepthClipEnable :: Bool
extendedDynamicState3ExtraPrimitiveOverestimationSize :: Bool
extendedDynamicState3ConservativeRasterizationMode :: Bool
extendedDynamicState3RasterizationStream :: Bool
extendedDynamicState3ColorWriteMask :: Bool
extendedDynamicState3ColorBlendEquation :: Bool
extendedDynamicState3ColorBlendEnable :: Bool
extendedDynamicState3LogicOpEnable :: Bool
extendedDynamicState3AlphaToOneEnable :: Bool
extendedDynamicState3AlphaToCoverageEnable :: Bool
extendedDynamicState3SampleMask :: Bool
extendedDynamicState3RasterizationSamples :: Bool
extendedDynamicState3PolygonMode :: Bool
extendedDynamicState3DepthClampEnable :: Bool
extendedDynamicState3TessellationDomainOrigin :: Bool
$sel:extendedDynamicState3ShadingRateImageEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3RepresentativeFragmentTestEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3CoverageReductionMode:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3CoverageModulationTable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3CoverageModulationTableEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3CoverageModulationMode:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3CoverageToColorLocation:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3CoverageToColorEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3ViewportSwizzle:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3ViewportWScalingEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3DepthClipNegativeOneToOne:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3LineStippleEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3LineRasterizationMode:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3ProvokingVertexMode:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3ColorBlendAdvanced:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3SampleLocationsEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3DepthClipEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3ExtraPrimitiveOverestimationSize:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3ConservativeRasterizationMode:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3RasterizationStream:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3ColorWriteMask:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3ColorBlendEquation:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3ColorBlendEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3LogicOpEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3AlphaToOneEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3AlphaToCoverageEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3SampleMask:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3RasterizationSamples:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3PolygonMode:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3DepthClampEnable:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
$sel:extendedDynamicState3TessellationDomainOrigin:PhysicalDeviceExtendedDynamicState3FeaturesEXT :: PhysicalDeviceExtendedDynamicState3FeaturesEXT -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_3_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3TessellationDomainOrigin))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3DepthClampEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3PolygonMode))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3RasterizationSamples))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3SampleMask))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3AlphaToCoverageEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3AlphaToOneEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3LogicOpEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ColorBlendEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ColorBlendEquation))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ColorWriteMask))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3RasterizationStream))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ConservativeRasterizationMode))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ExtraPrimitiveOverestimationSize))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3DepthClipEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3SampleLocationsEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ColorBlendAdvanced))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ProvokingVertexMode))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3LineRasterizationMode))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3LineStippleEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3DepthClipNegativeOneToOne))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ViewportWScalingEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ViewportSwizzle))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
108 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3CoverageToColorEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3CoverageToColorLocation))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
116 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3CoverageModulationMode))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3CoverageModulationTableEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
124 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3CoverageModulationTable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3CoverageReductionMode))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
132 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3RepresentativeFragmentTestEnable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
extendedDynamicState3ShadingRateImageEnable))
    IO b
f
  cStructSize :: Int
cStructSize = Int
144
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_3_FEATURES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
108 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
116 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
124 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
132 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceExtendedDynamicState3FeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
-> IO PhysicalDeviceExtendedDynamicState3FeaturesEXT
peekCStruct Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p = do
    "depthClampEnable" ::: Bool32
extendedDynamicState3TessellationDomainOrigin <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3DepthClampEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3PolygonMode <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3RasterizationSamples <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3SampleMask <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3AlphaToCoverageEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
36 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3AlphaToOneEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3LogicOpEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ColorBlendEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ColorBlendEquation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
52 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ColorWriteMask <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3RasterizationStream <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
60 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ConservativeRasterizationMode <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ExtraPrimitiveOverestimationSize <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
68 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3DepthClipEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3SampleLocationsEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
76 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ColorBlendAdvanced <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ProvokingVertexMode <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
84 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3LineRasterizationMode <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3LineStippleEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
92 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3DepthClipNegativeOneToOne <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ViewportWScalingEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
100 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ViewportSwizzle <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageToColorEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
108 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageToColorLocation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageModulationMode <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
116 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageModulationTableEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageModulationTable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
124 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageReductionMode <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
128 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3RepresentativeFragmentTestEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
132 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
extendedDynamicState3ShadingRateImageEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3FeaturesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
136 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceExtendedDynamicState3FeaturesEXT
PhysicalDeviceExtendedDynamicState3FeaturesEXT
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3TessellationDomainOrigin)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3DepthClampEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3PolygonMode)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3RasterizationSamples)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3SampleMask)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3AlphaToCoverageEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3AlphaToOneEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3LogicOpEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ColorBlendEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ColorBlendEquation)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ColorWriteMask)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3RasterizationStream)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ConservativeRasterizationMode)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ExtraPrimitiveOverestimationSize)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3DepthClipEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3SampleLocationsEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ColorBlendAdvanced)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ProvokingVertexMode)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3LineRasterizationMode)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3LineStippleEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3DepthClipNegativeOneToOne)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ViewportWScalingEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ViewportSwizzle)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageToColorEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageToColorLocation)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageModulationMode)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageModulationTableEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageModulationTable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3CoverageReductionMode)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3RepresentativeFragmentTestEnable)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
extendedDynamicState3ShadingRateImageEnable)

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

instance Zero PhysicalDeviceExtendedDynamicState3FeaturesEXT where
  zero :: PhysicalDeviceExtendedDynamicState3FeaturesEXT
zero = Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceExtendedDynamicState3FeaturesEXT
PhysicalDeviceExtendedDynamicState3FeaturesEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkPhysicalDeviceExtendedDynamicState3PropertiesEXT - Structure
-- describing capabilities of extended dynamic state
--
-- = Description
--
-- If the 'PhysicalDeviceExtendedDynamicState3PropertiesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceExtendedDynamicState3PropertiesEXT = PhysicalDeviceExtendedDynamicState3PropertiesEXT
  { -- | #limits-dynamicPrimitiveTopologyUnrestricted#
    -- @dynamicPrimitiveTopologyUnrestricted@ indicates that the implementation
    -- allows
    -- 'Vulkan.Core13.Promoted_From_VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopology'
    -- to use a different
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#drawing-primitive-topology-class primitive topology class>
    -- to the one specified in the active graphics pipeline.
    PhysicalDeviceExtendedDynamicState3PropertiesEXT -> Bool
dynamicPrimitiveTopologyUnrestricted :: Bool }
  deriving (Typeable, PhysicalDeviceExtendedDynamicState3PropertiesEXT
-> PhysicalDeviceExtendedDynamicState3PropertiesEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceExtendedDynamicState3PropertiesEXT
-> PhysicalDeviceExtendedDynamicState3PropertiesEXT -> Bool
$c/= :: PhysicalDeviceExtendedDynamicState3PropertiesEXT
-> PhysicalDeviceExtendedDynamicState3PropertiesEXT -> Bool
== :: PhysicalDeviceExtendedDynamicState3PropertiesEXT
-> PhysicalDeviceExtendedDynamicState3PropertiesEXT -> Bool
$c== :: PhysicalDeviceExtendedDynamicState3PropertiesEXT
-> PhysicalDeviceExtendedDynamicState3PropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceExtendedDynamicState3PropertiesEXT)
#endif
deriving instance Show PhysicalDeviceExtendedDynamicState3PropertiesEXT

instance ToCStruct PhysicalDeviceExtendedDynamicState3PropertiesEXT where
  withCStruct :: forall b.
PhysicalDeviceExtendedDynamicState3PropertiesEXT
-> (Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT -> IO b)
-> IO b
withCStruct PhysicalDeviceExtendedDynamicState3PropertiesEXT
x Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p PhysicalDeviceExtendedDynamicState3PropertiesEXT
x (Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT -> IO b
f Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
-> PhysicalDeviceExtendedDynamicState3PropertiesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p PhysicalDeviceExtendedDynamicState3PropertiesEXT{Bool
dynamicPrimitiveTopologyUnrestricted :: Bool
$sel:dynamicPrimitiveTopologyUnrestricted:PhysicalDeviceExtendedDynamicState3PropertiesEXT :: PhysicalDeviceExtendedDynamicState3PropertiesEXT -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_3_PROPERTIES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
dynamicPrimitiveTopologyUnrestricted))
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
-> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_3_PROPERTIES_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceExtendedDynamicState3PropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
-> IO PhysicalDeviceExtendedDynamicState3PropertiesEXT
peekCStruct Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p = do
    "depthClampEnable" ::: Bool32
dynamicPrimitiveTopologyUnrestricted <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExtendedDynamicState3PropertiesEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceExtendedDynamicState3PropertiesEXT
PhysicalDeviceExtendedDynamicState3PropertiesEXT
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
dynamicPrimitiveTopologyUnrestricted)

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

instance Zero PhysicalDeviceExtendedDynamicState3PropertiesEXT where
  zero :: PhysicalDeviceExtendedDynamicState3PropertiesEXT
zero = Bool -> PhysicalDeviceExtendedDynamicState3PropertiesEXT
PhysicalDeviceExtendedDynamicState3PropertiesEXT
           forall a. Zero a => a
zero


-- | VkColorBlendEquationEXT - Structure specifying the color blend factors
-- and operations for an attachment
--
-- == Valid Usage
--
-- -   #VUID-VkColorBlendEquationEXT-dualSrcBlend-07357# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-dualSrcBlend dualSrcBlend>
--     feature is not enabled, @srcColorBlendFactor@ /must/ not be
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_COLOR',
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_COLOR',
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_ALPHA', or
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA'
--
-- -   #VUID-VkColorBlendEquationEXT-dualSrcBlend-07358# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-dualSrcBlend dualSrcBlend>
--     feature is not enabled, @dstColorBlendFactor@ /must/ not be
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_COLOR',
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_COLOR',
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_ALPHA', or
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA'
--
-- -   #VUID-VkColorBlendEquationEXT-dualSrcBlend-07359# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-dualSrcBlend dualSrcBlend>
--     feature is not enabled, @srcAlphaBlendFactor@ /must/ not be
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_COLOR',
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_COLOR',
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_ALPHA', or
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA'
--
-- -   #VUID-VkColorBlendEquationEXT-dualSrcBlend-07360# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-dualSrcBlend dualSrcBlend>
--     feature is not enabled, @dstAlphaBlendFactor@ /must/ not be
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_COLOR',
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_COLOR',
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_SRC1_ALPHA', or
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA'
--
-- -   #VUID-VkColorBlendEquationEXT-colorBlendOp-07361# @colorBlendOp@ and
--     @alphaBlendOp@ /must/ not be
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_ZERO_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_OVER_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_OVER_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_IN_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_IN_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_OUT_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_OUT_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_SRC_ATOP_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_DST_ATOP_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_XOR_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_INVERT_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_INVERT_RGB_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_LINEARDODGE_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_LINEARBURN_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_VIVIDLIGHT_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_LINEARLIGHT_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PINLIGHT_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_HARDMIX_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PLUS_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PLUS_CLAMPED_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PLUS_CLAMPED_ALPHA_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_PLUS_DARKER_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_MINUS_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_MINUS_CLAMPED_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_CONTRAST_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_INVERT_OVG_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_RED_EXT',
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_GREEN_EXT', or
--     'Vulkan.Core10.Enums.BlendOp.BLEND_OP_BLUE_EXT'
--
-- -   #VUID-VkColorBlendEquationEXT-constantAlphaColorBlendFactors-07362#
--     If the @VK_KHR_portability_subset@ extension is enabled, and
--     'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetFeaturesKHR'::@constantAlphaColorBlendFactors@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', @srcColorBlendFactor@
--     /must/ not be
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_ALPHA' or
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_ALPHA'
--
-- -   #VUID-VkColorBlendEquationEXT-constantAlphaColorBlendFactors-07363#
--     If the @VK_KHR_portability_subset@ extension is enabled, and
--     'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetFeaturesKHR'::@constantAlphaColorBlendFactors@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', @dstColorBlendFactor@
--     /must/ not be
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_CONSTANT_ALPHA' or
--     'Vulkan.Core10.Enums.BlendFactor.BLEND_FACTOR_ONE_MINUS_CONSTANT_ALPHA'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkColorBlendEquationEXT-srcColorBlendFactor-parameter#
--     @srcColorBlendFactor@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendFactor.BlendFactor' value
--
-- -   #VUID-VkColorBlendEquationEXT-dstColorBlendFactor-parameter#
--     @dstColorBlendFactor@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendFactor.BlendFactor' value
--
-- -   #VUID-VkColorBlendEquationEXT-colorBlendOp-parameter# @colorBlendOp@
--     /must/ be a valid 'Vulkan.Core10.Enums.BlendOp.BlendOp' value
--
-- -   #VUID-VkColorBlendEquationEXT-srcAlphaBlendFactor-parameter#
--     @srcAlphaBlendFactor@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendFactor.BlendFactor' value
--
-- -   #VUID-VkColorBlendEquationEXT-dstAlphaBlendFactor-parameter#
--     @dstAlphaBlendFactor@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendFactor.BlendFactor' value
--
-- -   #VUID-VkColorBlendEquationEXT-alphaBlendOp-parameter# @alphaBlendOp@
--     /must/ be a valid 'Vulkan.Core10.Enums.BlendOp.BlendOp' value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Enums.BlendFactor.BlendFactor',
-- 'Vulkan.Core10.Enums.BlendOp.BlendOp', 'cmdSetColorBlendEquationEXT'
data ColorBlendEquationEXT = ColorBlendEquationEXT
  { -- | @srcColorBlendFactor@ selects which blend factor is used to determine
    -- the source factors (Sr,Sg,Sb).
    ColorBlendEquationEXT -> BlendFactor
srcColorBlendFactor :: BlendFactor
  , -- | @dstColorBlendFactor@ selects which blend factor is used to determine
    -- the destination factors (Dr,Dg,Db).
    ColorBlendEquationEXT -> BlendFactor
dstColorBlendFactor :: BlendFactor
  , -- | @colorBlendOp@ selects which blend operation is used to calculate the
    -- RGB values to write to the color attachment.
    ColorBlendEquationEXT -> BlendOp
colorBlendOp :: BlendOp
  , -- | @srcAlphaBlendFactor@ selects which blend factor is used to determine
    -- the source factor Sa.
    ColorBlendEquationEXT -> BlendFactor
srcAlphaBlendFactor :: BlendFactor
  , -- | @dstAlphaBlendFactor@ selects which blend factor is used to determine
    -- the destination factor Da.
    ColorBlendEquationEXT -> BlendFactor
dstAlphaBlendFactor :: BlendFactor
  , -- | @alphaBlendOp@ selects which blend operation is use to calculate the
    -- alpha values to write to the color attachment.
    ColorBlendEquationEXT -> BlendOp
alphaBlendOp :: BlendOp
  }
  deriving (Typeable, ColorBlendEquationEXT -> ColorBlendEquationEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColorBlendEquationEXT -> ColorBlendEquationEXT -> Bool
$c/= :: ColorBlendEquationEXT -> ColorBlendEquationEXT -> Bool
== :: ColorBlendEquationEXT -> ColorBlendEquationEXT -> Bool
$c== :: ColorBlendEquationEXT -> ColorBlendEquationEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ColorBlendEquationEXT)
#endif
deriving instance Show ColorBlendEquationEXT

instance ToCStruct ColorBlendEquationEXT where
  withCStruct :: forall b.
ColorBlendEquationEXT
-> (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT) -> IO b)
-> IO b
withCStruct ColorBlendEquationEXT
x ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p ColorBlendEquationEXT
x (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT) -> IO b
f "pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p)
  pokeCStruct :: forall b.
("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
-> ColorBlendEquationEXT -> IO b -> IO b
pokeCStruct "pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p ColorBlendEquationEXT{BlendOp
BlendFactor
alphaBlendOp :: BlendOp
dstAlphaBlendFactor :: BlendFactor
srcAlphaBlendFactor :: BlendFactor
colorBlendOp :: BlendOp
dstColorBlendFactor :: BlendFactor
srcColorBlendFactor :: BlendFactor
$sel:alphaBlendOp:ColorBlendEquationEXT :: ColorBlendEquationEXT -> BlendOp
$sel:dstAlphaBlendFactor:ColorBlendEquationEXT :: ColorBlendEquationEXT -> BlendFactor
$sel:srcAlphaBlendFactor:ColorBlendEquationEXT :: ColorBlendEquationEXT -> BlendFactor
$sel:colorBlendOp:ColorBlendEquationEXT :: ColorBlendEquationEXT -> BlendOp
$sel:dstColorBlendFactor:ColorBlendEquationEXT :: ColorBlendEquationEXT -> BlendFactor
$sel:srcColorBlendFactor:ColorBlendEquationEXT :: ColorBlendEquationEXT -> BlendFactor
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr BlendFactor)) (BlendFactor
srcColorBlendFactor)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr BlendFactor)) (BlendFactor
dstColorBlendFactor)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr BlendOp)) (BlendOp
colorBlendOp)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr BlendFactor)) (BlendFactor
srcAlphaBlendFactor)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr BlendFactor)) (BlendFactor
dstAlphaBlendFactor)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr BlendOp)) (BlendOp
alphaBlendOp)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
4
  pokeZeroCStruct :: forall b.
("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
-> IO b -> IO b
pokeZeroCStruct "pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr BlendFactor)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr BlendFactor)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr BlendOp)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr BlendFactor)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr BlendFactor)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr BlendOp)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ColorBlendEquationEXT where
  peekCStruct :: ("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT)
-> IO ColorBlendEquationEXT
peekCStruct "pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p = do
    BlendFactor
srcColorBlendFactor <- forall a. Storable a => Ptr a -> IO a
peek @BlendFactor (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr BlendFactor))
    BlendFactor
dstColorBlendFactor <- forall a. Storable a => Ptr a -> IO a
peek @BlendFactor (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr BlendFactor))
    BlendOp
colorBlendOp <- forall a. Storable a => Ptr a -> IO a
peek @BlendOp (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr BlendOp))
    BlendFactor
srcAlphaBlendFactor <- forall a. Storable a => Ptr a -> IO a
peek @BlendFactor (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr BlendFactor))
    BlendFactor
dstAlphaBlendFactor <- forall a. Storable a => Ptr a -> IO a
peek @BlendFactor (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr BlendFactor))
    BlendOp
alphaBlendOp <- forall a. Storable a => Ptr a -> IO a
peek @BlendOp (("pColorBlendEquations" ::: Ptr ColorBlendEquationEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr BlendOp))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ BlendFactor
-> BlendFactor
-> BlendOp
-> BlendFactor
-> BlendFactor
-> BlendOp
-> ColorBlendEquationEXT
ColorBlendEquationEXT
             BlendFactor
srcColorBlendFactor
             BlendFactor
dstColorBlendFactor
             BlendOp
colorBlendOp
             BlendFactor
srcAlphaBlendFactor
             BlendFactor
dstAlphaBlendFactor
             BlendOp
alphaBlendOp

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

instance Zero ColorBlendEquationEXT where
  zero :: ColorBlendEquationEXT
zero = BlendFactor
-> BlendFactor
-> BlendOp
-> BlendFactor
-> BlendFactor
-> BlendOp
-> ColorBlendEquationEXT
ColorBlendEquationEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkColorBlendAdvancedEXT - Structure specifying the advanced blend
-- operation parameters for an attachment
--
-- == Valid Usage
--
-- -   #VUID-VkColorBlendAdvancedEXT-srcPremultiplied-07505# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-advancedBlendNonPremultipliedSrcColor non-premultiplied source color>
--     property is not supported, @srcPremultiplied@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   #VUID-VkColorBlendAdvancedEXT-dstPremultiplied-07506# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-advancedBlendNonPremultipliedDstColor non-premultiplied destination color>
--     property is not supported, @dstPremultiplied@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   #VUID-VkColorBlendAdvancedEXT-blendOverlap-07507# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-advancedBlendCorrelatedOverlap correlated overlap>
--     property is not supported, @blendOverlap@ /must/ be
--     'Vulkan.Extensions.VK_EXT_blend_operation_advanced.BLEND_OVERLAP_UNCORRELATED_EXT'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkColorBlendAdvancedEXT-advancedBlendOp-parameter#
--     @advancedBlendOp@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendOp.BlendOp' value
--
-- -   #VUID-VkColorBlendAdvancedEXT-blendOverlap-parameter# @blendOverlap@
--     /must/ be a valid
--     'Vulkan.Extensions.VK_EXT_blend_operation_advanced.BlendOverlapEXT'
--     value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_extended_dynamic_state3 VK_EXT_extended_dynamic_state3>,
-- 'Vulkan.Core10.Enums.BlendOp.BlendOp',
-- 'Vulkan.Extensions.VK_EXT_blend_operation_advanced.BlendOverlapEXT',
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'cmdSetColorBlendAdvancedEXT'
data ColorBlendAdvancedEXT = ColorBlendAdvancedEXT
  { -- | @advancedBlendOp@ selects which blend operation is used to calculate the
    -- RGB values to write to the color attachment.
    ColorBlendAdvancedEXT -> BlendOp
advancedBlendOp :: BlendOp
  , -- | @srcPremultiplied@ specifies whether the source color of the blend
    -- operation is treated as premultiplied.
    ColorBlendAdvancedEXT -> Bool
srcPremultiplied :: Bool
  , -- | @dstPremultiplied@ specifies whether the destination color of the blend
    -- operation is treated as premultiplied.
    ColorBlendAdvancedEXT -> Bool
dstPremultiplied :: Bool
  , -- | @blendOverlap@ is a
    -- 'Vulkan.Extensions.VK_EXT_blend_operation_advanced.BlendOverlapEXT'
    -- value specifying how the source and destination sample’s coverage is
    -- correlated.
    ColorBlendAdvancedEXT -> BlendOverlapEXT
blendOverlap :: BlendOverlapEXT
  , -- | @clampResults@ specifies the results must be clamped to the [0,1] range
    -- before writing to the attachment, which is useful when the attachment
    -- format is not normalized fixed-point.
    ColorBlendAdvancedEXT -> Bool
clampResults :: Bool
  }
  deriving (Typeable, ColorBlendAdvancedEXT -> ColorBlendAdvancedEXT -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColorBlendAdvancedEXT -> ColorBlendAdvancedEXT -> Bool
$c/= :: ColorBlendAdvancedEXT -> ColorBlendAdvancedEXT -> Bool
== :: ColorBlendAdvancedEXT -> ColorBlendAdvancedEXT -> Bool
$c== :: ColorBlendAdvancedEXT -> ColorBlendAdvancedEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ColorBlendAdvancedEXT)
#endif
deriving instance Show ColorBlendAdvancedEXT

instance ToCStruct ColorBlendAdvancedEXT where
  withCStruct :: forall b.
ColorBlendAdvancedEXT
-> (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT) -> IO b)
-> IO b
withCStruct ColorBlendAdvancedEXT
x ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
20 forall a b. (a -> b) -> a -> b
$ \"pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p ColorBlendAdvancedEXT
x (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT) -> IO b
f "pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p)
  pokeCStruct :: forall b.
("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
-> ColorBlendAdvancedEXT -> IO b -> IO b
pokeCStruct "pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p ColorBlendAdvancedEXT{Bool
BlendOverlapEXT
BlendOp
clampResults :: Bool
blendOverlap :: BlendOverlapEXT
dstPremultiplied :: Bool
srcPremultiplied :: Bool
advancedBlendOp :: BlendOp
$sel:clampResults:ColorBlendAdvancedEXT :: ColorBlendAdvancedEXT -> Bool
$sel:blendOverlap:ColorBlendAdvancedEXT :: ColorBlendAdvancedEXT -> BlendOverlapEXT
$sel:dstPremultiplied:ColorBlendAdvancedEXT :: ColorBlendAdvancedEXT -> Bool
$sel:srcPremultiplied:ColorBlendAdvancedEXT :: ColorBlendAdvancedEXT -> Bool
$sel:advancedBlendOp:ColorBlendAdvancedEXT :: ColorBlendAdvancedEXT -> BlendOp
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr BlendOp)) (BlendOp
advancedBlendOp)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
srcPremultiplied))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
dstPremultiplied))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr BlendOverlapEXT)) (BlendOverlapEXT
blendOverlap)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (Bool
clampResults))
    IO b
f
  cStructSize :: Int
cStructSize = Int
20
  cStructAlignment :: Int
cStructAlignment = Int
4
  pokeZeroCStruct :: forall b.
("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
-> IO b -> IO b
pokeZeroCStruct "pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr BlendOp)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr BlendOverlapEXT)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> "depthClampEnable" ::: Bool32
boolToBool32 (forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct ColorBlendAdvancedEXT where
  peekCStruct :: ("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT)
-> IO ColorBlendAdvancedEXT
peekCStruct "pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p = do
    BlendOp
advancedBlendOp <- forall a. Storable a => Ptr a -> IO a
peek @BlendOp (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr BlendOp))
    "depthClampEnable" ::: Bool32
srcPremultiplied <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Bool32))
    "depthClampEnable" ::: Bool32
dstPremultiplied <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Bool32))
    BlendOverlapEXT
blendOverlap <- forall a. Storable a => Ptr a -> IO a
peek @BlendOverlapEXT (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr BlendOverlapEXT))
    "depthClampEnable" ::: Bool32
clampResults <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pColorBlendAdvanced" ::: Ptr ColorBlendAdvancedEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ BlendOp
-> Bool -> Bool -> BlendOverlapEXT -> Bool -> ColorBlendAdvancedEXT
ColorBlendAdvancedEXT
             BlendOp
advancedBlendOp
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
srcPremultiplied)
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
dstPremultiplied)
             BlendOverlapEXT
blendOverlap
             (("depthClampEnable" ::: Bool32) -> Bool
bool32ToBool "depthClampEnable" ::: Bool32
clampResults)

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

instance Zero ColorBlendAdvancedEXT where
  zero :: ColorBlendAdvancedEXT
zero = BlendOp
-> Bool -> Bool -> BlendOverlapEXT -> Bool -> ColorBlendAdvancedEXT
ColorBlendAdvancedEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


type EXT_EXTENDED_DYNAMIC_STATE_3_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_EXTENDED_DYNAMIC_STATE_3_SPEC_VERSION"
pattern EXT_EXTENDED_DYNAMIC_STATE_3_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_EXTENDED_DYNAMIC_STATE_3_SPEC_VERSION :: forall a. Integral a => a
$mEXT_EXTENDED_DYNAMIC_STATE_3_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_EXTENDED_DYNAMIC_STATE_3_SPEC_VERSION = 2


type EXT_EXTENDED_DYNAMIC_STATE_3_EXTENSION_NAME = "VK_EXT_extended_dynamic_state3"

-- No documentation found for TopLevel "VK_EXT_EXTENDED_DYNAMIC_STATE_3_EXTENSION_NAME"
pattern EXT_EXTENDED_DYNAMIC_STATE_3_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_EXTENDED_DYNAMIC_STATE_3_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_EXTENDED_DYNAMIC_STATE_3_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_EXTENDED_DYNAMIC_STATE_3_EXTENSION_NAME = "VK_EXT_extended_dynamic_state3"