{-# language CPP #-}
module Vulkan.Core10.Pipeline  ( createGraphicsPipelines
                               , withGraphicsPipelines
                               , createComputePipelines
                               , withComputePipelines
                               , destroyPipeline
                               , Viewport(..)
                               , SpecializationMapEntry(..)
                               , SpecializationInfo(..)
                               , PipelineShaderStageCreateInfo(..)
                               , ComputePipelineCreateInfo(..)
                               , VertexInputBindingDescription(..)
                               , VertexInputAttributeDescription(..)
                               , PipelineVertexInputStateCreateInfo(..)
                               , PipelineInputAssemblyStateCreateInfo(..)
                               , PipelineTessellationStateCreateInfo(..)
                               , PipelineViewportStateCreateInfo(..)
                               , PipelineRasterizationStateCreateInfo(..)
                               , PipelineMultisampleStateCreateInfo(..)
                               , PipelineColorBlendAttachmentState(..)
                               , PipelineColorBlendStateCreateInfo(..)
                               , PipelineDynamicStateCreateInfo(..)
                               , StencilOpState(..)
                               , PipelineDepthStencilStateCreateInfo(..)
                               , GraphicsPipelineCreateInfo(..)
                               , Pipeline(..)
                               , PipelineLayoutCreateFlags(..)
                               , PipelineDepthStencilStateCreateFlags(..)
                               , PipelineDynamicStateCreateFlags(..)
                               , PipelineColorBlendStateCreateFlags(..)
                               , PipelineMultisampleStateCreateFlags(..)
                               , PipelineRasterizationStateCreateFlags(..)
                               , PipelineViewportStateCreateFlags(..)
                               , PipelineTessellationStateCreateFlags(..)
                               , PipelineInputAssemblyStateCreateFlags(..)
                               , PipelineVertexInputStateCreateFlags(..)
                               , PrimitiveTopology(..)
                               , CompareOp(..)
                               , PolygonMode(..)
                               , FrontFace(..)
                               , BlendFactor(..)
                               , BlendOp(..)
                               , StencilOp(..)
                               , LogicOp(..)
                               , VertexInputRate(..)
                               , DynamicState(..)
                               , CullModeFlagBits(..)
                               , CullModeFlags
                               , ShaderStageFlagBits(..)
                               , ShaderStageFlags
                               , PipelineCreateFlagBits(..)
                               , PipelineCreateFlags
                               , PipelineShaderStageCreateFlagBits(..)
                               , PipelineShaderStageCreateFlags
                               , ColorComponentFlagBits(..)
                               , ColorComponentFlags
                               , SampleMask
                               ) where

import Vulkan.CStruct.Utils (FixedArray)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Foldable (traverse_)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import Foreign.Marshal.Utils (maybePeek)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import qualified Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.ByteString (packCString)
import Data.ByteString (useAsCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import qualified Data.Vector (null)
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(CFloat))
import Foreign.C.Types (CSize)
import Foreign.C.Types (CSize(CSize))
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Word (Word64)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.CStruct.Extends (peekSomeCStruct)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.CStruct.Extends (withSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.Enums.BlendFactor (BlendFactor)
import Vulkan.Core10.Enums.BlendOp (BlendOp)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Enums.ColorComponentFlagBits (ColorComponentFlags)
import Vulkan.Core10.Enums.CompareOp (CompareOp)
import Vulkan.Core10.Enums.CullModeFlagBits (CullModeFlags)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkCreateComputePipelines))
import Vulkan.Dynamic (DeviceCmds(pVkCreateGraphicsPipelines))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyPipeline))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.Enums.DynamicState (DynamicState)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.FrontFace (FrontFace)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_device_generated_commands (GraphicsPipelineShaderGroupsCreateInfoNV)
import Vulkan.Core10.Enums.LogicOp (LogicOp)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Handles (Pipeline)
import Vulkan.Core10.Handles (Pipeline(..))
import Vulkan.Core10.Handles (PipelineCache)
import Vulkan.Core10.Handles (PipelineCache(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_blend_operation_advanced (PipelineColorBlendAdvancedStateCreateInfoEXT)
import Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags (PipelineColorBlendStateCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_AMD_pipeline_compiler_control (PipelineCompilerControlCreateInfoAMD)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_framebuffer_mixed_samples (PipelineCoverageModulationStateCreateInfoNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_coverage_reduction_mode (PipelineCoverageReductionStateCreateInfoNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_fragment_coverage_to_color (PipelineCoverageToColorStateCreateInfoNV)
import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_pipeline_creation_feedback (PipelineCreationFeedbackCreateInfoEXT)
import Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags (PipelineDepthStencilStateCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_discard_rectangles (PipelineDiscardRectangleStateCreateInfoEXT)
import Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags (PipelineDynamicStateCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_fragment_shading_rate (PipelineFragmentShadingRateStateCreateInfoKHR)
import Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags (PipelineInputAssemblyStateCreateFlags)
import Vulkan.Core10.Handles (PipelineLayout)
import Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags (PipelineMultisampleStateCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_conservative_rasterization (PipelineRasterizationConservativeStateCreateInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_depth_clip_enable (PipelineRasterizationDepthClipStateCreateInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_line_rasterization (PipelineRasterizationLineStateCreateInfoEXT)
import Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags (PipelineRasterizationStateCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_AMD_rasterization_order (PipelineRasterizationStateRasterizationOrderAMD)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_transform_feedback (PipelineRasterizationStateStreamCreateInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_representative_fragment_test (PipelineRepresentativeFragmentTestStateCreateInfoNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_sample_locations (PipelineSampleLocationsStateCreateInfoEXT)
import Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits (PipelineShaderStageCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_subgroup_size_control (PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_maintenance2 (PipelineTessellationDomainOriginStateCreateInfo)
import Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags (PipelineTessellationStateCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_vertex_attribute_divisor (PipelineVertexInputDivisorStateCreateInfoEXT)
import Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags (PipelineVertexInputStateCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_shading_rate_image (PipelineViewportCoarseSampleOrderStateCreateInfoNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_scissor_exclusive (PipelineViewportExclusiveScissorStateCreateInfoNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_shading_rate_image (PipelineViewportShadingRateImageStateCreateInfoNV)
import Vulkan.Core10.Enums.PipelineViewportStateCreateFlags (PipelineViewportStateCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_viewport_swizzle (PipelineViewportSwizzleStateCreateInfoNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_clip_space_w_scaling (PipelineViewportWScalingStateCreateInfoNV)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.PolygonMode (PolygonMode)
import Vulkan.Core10.Enums.PrimitiveTopology (PrimitiveTopology)
import Vulkan.Core10.FundamentalTypes (Rect2D)
import Vulkan.Core10.Handles (RenderPass)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits(SampleCountFlagBits))
import Vulkan.Core10.FundamentalTypes (SampleMask)
import Vulkan.Core10.Handles (ShaderModule)
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlagBits)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.CStruct.Extends (SomeStruct(..))
import Vulkan.Core10.Enums.StencilOp (StencilOp)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Core10.Enums.VertexInputRate (VertexInputRate)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COMPUTE_PIPELINE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_GRAPHICS_PIPELINE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_DEPTH_STENCIL_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_DYNAMIC_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_INPUT_ASSEMBLY_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_MULTISAMPLE_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_TESSELLATION_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_VIEWPORT_STATE_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Enums.BlendFactor (BlendFactor(..))
import Vulkan.Core10.Enums.BlendOp (BlendOp(..))
import Vulkan.Core10.Enums.ColorComponentFlagBits (ColorComponentFlagBits(..))
import Vulkan.Core10.Enums.ColorComponentFlagBits (ColorComponentFlags)
import Vulkan.Core10.Enums.CompareOp (CompareOp(..))
import Vulkan.Core10.Enums.CullModeFlagBits (CullModeFlagBits(..))
import Vulkan.Core10.Enums.CullModeFlagBits (CullModeFlags)
import Vulkan.Core10.Enums.DynamicState (DynamicState(..))
import Vulkan.Core10.Enums.FrontFace (FrontFace(..))
import Vulkan.Core10.Enums.LogicOp (LogicOp(..))
import Vulkan.Core10.Handles (Pipeline(..))
import Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags (PipelineColorBlendStateCreateFlags(..))
import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlagBits(..))
import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlags)
import Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags (PipelineDepthStencilStateCreateFlags(..))
import Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags (PipelineDynamicStateCreateFlags(..))
import Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags (PipelineInputAssemblyStateCreateFlags(..))
import Vulkan.Core10.Enums.PipelineLayoutCreateFlags (PipelineLayoutCreateFlags(..))
import Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags (PipelineMultisampleStateCreateFlags(..))
import Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags (PipelineRasterizationStateCreateFlags(..))
import Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits (PipelineShaderStageCreateFlagBits(..))
import Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits (PipelineShaderStageCreateFlags)
import Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags (PipelineTessellationStateCreateFlags(..))
import Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags (PipelineVertexInputStateCreateFlags(..))
import Vulkan.Core10.Enums.PipelineViewportStateCreateFlags (PipelineViewportStateCreateFlags(..))
import Vulkan.Core10.Enums.PolygonMode (PolygonMode(..))
import Vulkan.Core10.Enums.PrimitiveTopology (PrimitiveTopology(..))
import Vulkan.Core10.FundamentalTypes (SampleMask)
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlagBits(..))
import Vulkan.Core10.Enums.ShaderStageFlagBits (ShaderStageFlags)
import Vulkan.Core10.Enums.StencilOp (StencilOp(..))
import Vulkan.Core10.Enums.VertexInputRate (VertexInputRate(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateGraphicsPipelines
  :: FunPtr (Ptr Device_T -> PipelineCache -> Word32 -> Ptr (SomeStruct GraphicsPipelineCreateInfo) -> Ptr AllocationCallbacks -> Ptr Pipeline -> IO Result) -> Ptr Device_T -> PipelineCache -> Word32 -> Ptr (SomeStruct GraphicsPipelineCreateInfo) -> Ptr AllocationCallbacks -> Ptr Pipeline -> IO Result

-- | vkCreateGraphicsPipelines - Create graphics pipelines
--
-- = Description
--
-- The 'GraphicsPipelineCreateInfo' structure includes an array of shader
-- create info structures containing all the desired active shader stages,
-- as well as creation info to define all relevant fixed-function stages,
-- and a pipeline layout.
--
-- == Valid Usage
--
-- -   If the @flags@ member of any element of @pCreateInfos@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and the @basePipelineIndex@ member of that same element is not
--     @-1@, @basePipelineIndex@ /must/ be less than the index into
--     @pCreateInfos@ that corresponds to that element
--
-- -   If the @flags@ member of any element of @pCreateInfos@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, the base pipeline /must/ have been created with the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT'
--     flag set
--
-- -   If @pipelineCache@ was created with
--     'Vulkan.Core10.Enums.PipelineCacheCreateFlagBits.PIPELINE_CACHE_CREATE_EXTERNALLY_SYNCHRONIZED_BIT_EXT',
--     host access to @pipelineCache@ /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-threadingbehavior externally synchronized>
--
-- Note
--
-- An implicit cache may be provided by the implementation or a layer. For
-- this reason, it is still valid to set
-- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT'
-- on @flags@ for any element of @pCreateInfos@ while passing
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE' for @pipelineCache@.
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @pipelineCache@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @pipelineCache@ /must/ be a valid
--     'Vulkan.Core10.Handles.PipelineCache' handle
--
-- -   @pCreateInfos@ /must/ be a valid pointer to an array of
--     @createInfoCount@ valid 'GraphicsPipelineCreateInfo' structures
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pPipelines@ /must/ be a valid pointer to an array of
--     @createInfoCount@ 'Vulkan.Core10.Handles.Pipeline' handles
--
-- -   @createInfoCount@ /must/ be greater than @0@
--
-- -   If @pipelineCache@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.PIPELINE_COMPILE_REQUIRED_EXT'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_INVALID_SHADER_NV'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Core10.Handles.Pipeline', 'Vulkan.Core10.Handles.PipelineCache'
createGraphicsPipelines :: forall io
                         . (MonadIO io)
                        => -- | @device@ is the logical device that creates the graphics pipelines.
                           Device
                        -> -- | @pipelineCache@ is either 'Vulkan.Core10.APIConstants.NULL_HANDLE',
                           -- indicating that pipeline caching is disabled; or the handle of a valid
                           -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipelines-cache pipeline cache>
                           -- object, in which case use of that cache is enabled for the duration of
                           -- the command.
                           PipelineCache
                        -> -- | @pCreateInfos@ is a pointer to an array of 'GraphicsPipelineCreateInfo'
                           -- structures.
                           ("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
                        -> -- | @pAllocator@ controls host memory allocation as described in the
                           -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                           -- chapter.
                           ("allocator" ::: Maybe AllocationCallbacks)
                        -> io (Result, ("pipelines" ::: Vector Pipeline))
createGraphicsPipelines :: Device
-> PipelineCache
-> ("createInfos"
    ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io (Result, "pipelines" ::: Vector Pipeline)
createGraphicsPipelines device :: Device
device pipelineCache :: PipelineCache
pipelineCache createInfos :: "createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo)
createInfos allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO (Result, "pipelines" ::: Vector Pipeline)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "pipelines" ::: Vector Pipeline)
 -> io (Result, "pipelines" ::: Vector Pipeline))
-> (ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      (Result, "pipelines" ::: Vector Pipeline)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "pipelines" ::: Vector Pipeline)
  IO
  (Result, "pipelines" ::: Vector Pipeline)
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "pipelines" ::: Vector Pipeline)
   IO
   (Result, "pipelines" ::: Vector Pipeline)
 -> io (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateGraphicsPipelinesPtr :: FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
vkCreateGraphicsPipelinesPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("createInfoCount" ::: Word32)
      -> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pPipelines" ::: Ptr Pipeline)
      -> IO Result)
pVkCreateGraphicsPipelines (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
vkCreateGraphicsPipelinesPtr FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("createInfoCount" ::: Word32)
      -> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pPipelines" ::: Ptr Pipeline)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCreateGraphicsPipelines is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateGraphicsPipelines' :: Ptr Device_T
-> PipelineCache
-> ("createInfoCount" ::: Word32)
-> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelines" ::: Ptr Pipeline)
-> IO Result
vkCreateGraphicsPipelines' = FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
-> Ptr Device_T
-> PipelineCache
-> ("createInfoCount" ::: Word32)
-> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelines" ::: Ptr Pipeline)
-> IO Result
mkVkCreateGraphicsPipelines FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
vkCreateGraphicsPipelinesPtr
  Ptr (GraphicsPipelineCreateInfo Any)
pPCreateInfos <- ((Ptr (GraphicsPipelineCreateInfo Any)
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Ptr (GraphicsPipelineCreateInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (GraphicsPipelineCreateInfo Any)
   -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      (Ptr (GraphicsPipelineCreateInfo Any)))
-> ((Ptr (GraphicsPipelineCreateInfo Any)
     -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Ptr (GraphicsPipelineCreateInfo Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr (GraphicsPipelineCreateInfo Any)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(GraphicsPipelineCreateInfo _) ((("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo)
createInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 144) 8
  (Int
 -> SomeStruct GraphicsPipelineCreateInfo
 -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> ("createInfos"
    ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct GraphicsPipelineCreateInfo
e -> ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall a b. (a -> b) -> a -> b
$ ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
-> SomeStruct GraphicsPipelineCreateInfo
-> IO (Result, "pipelines" ::: Vector Pipeline)
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (GraphicsPipelineCreateInfo Any)
-> "pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (GraphicsPipelineCreateInfo Any)
pPCreateInfos Ptr (GraphicsPipelineCreateInfo Any)
-> Int -> Ptr (GraphicsPipelineCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (144 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (GraphicsPipelineCreateInfo _))) (SomeStruct GraphicsPipelineCreateInfo
e) (IO (Result, "pipelines" ::: Vector Pipeline)
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> (() -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
-> () -> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ ())) ("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo)
createInfos)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks)
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks)
     -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pPipelines" ::: Ptr Pipeline
pPPipelines <- ((("pPipelines" ::: Ptr Pipeline)
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pPipelines" ::: Ptr Pipeline)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPipelines" ::: Ptr Pipeline)
   -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      ("pPipelines" ::: Ptr Pipeline))
-> ((("pPipelines" ::: Ptr Pipeline)
     -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pPipelines" ::: Ptr Pipeline)
forall a b. (a -> b) -> a -> b
$ IO ("pPipelines" ::: Ptr Pipeline)
-> (("pPipelines" ::: Ptr Pipeline) -> IO ())
-> (("pPipelines" ::: Ptr Pipeline)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPipelines" ::: Ptr Pipeline)
forall a. Int -> IO (Ptr a)
callocBytes @Pipeline ((("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
 -> Int)
-> ("createInfos"
    ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> Int
forall a b. (a -> b) -> a -> b
$ ("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo)
createInfos)) :: Word32))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8)) ("pPipelines" ::: Ptr Pipeline) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT (Result, "pipelines" ::: Vector Pipeline) IO Result)
-> IO Result
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> PipelineCache
-> ("createInfoCount" ::: Word32)
-> ("pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelines" ::: Ptr Pipeline)
-> IO Result
vkCreateGraphicsPipelines' (Device -> Ptr Device_T
deviceHandle (Device
device)) (PipelineCache
pipelineCache) ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
 -> Int)
-> ("createInfos"
    ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> Int
forall a b. (a -> b) -> a -> b
$ ("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo)
createInfos)) :: Word32)) (Ptr (GraphicsPipelineCreateInfo Any)
-> "pCreateInfos" ::: Ptr (SomeStruct GraphicsPipelineCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (GraphicsPipelineCreateInfo Any)
pPCreateInfos)) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pPipelines" ::: Ptr Pipeline
pPPipelines)
  IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  "pipelines" ::: Vector Pipeline
pPipelines <- IO ("pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pipelines" ::: Vector Pipeline)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("pipelines" ::: Vector Pipeline)
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      ("pipelines" ::: Vector Pipeline))
-> IO ("pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> IO Pipeline) -> IO ("pipelines" ::: Vector Pipeline)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
 -> Int)
-> ("createInfos"
    ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> Int
forall a b. (a -> b) -> a -> b
$ ("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo)
createInfos)) :: Word32))) (\i :: Int
i -> ("pPipelines" ::: Ptr Pipeline) -> IO Pipeline
forall a. Storable a => Ptr a -> IO a
peek @Pipeline (("pPipelines" ::: Ptr Pipeline
pPPipelines ("pPipelines" ::: Ptr Pipeline)
-> Int -> "pPipelines" ::: Ptr Pipeline
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Pipeline)))
  (Result, "pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "pipelines" ::: Vector Pipeline)
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      (Result, "pipelines" ::: Vector Pipeline))
-> (Result, "pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ (Result
r, "pipelines" ::: Vector Pipeline
pPipelines)

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createGraphicsPipelines' and 'destroyPipeline'
--
-- To ensure that 'destroyPipeline' is always called: pass
-- 'Control.Exception.bracket' (or the allocate function from your
-- favourite resource management library) as the first argument.
-- To just extract the pair pass '(,)' as the first argument.
--
withGraphicsPipelines :: forall io r . MonadIO io => Device -> PipelineCache -> Vector (SomeStruct GraphicsPipelineCreateInfo) -> Maybe AllocationCallbacks -> (io (Result, Vector Pipeline) -> ((Result, Vector Pipeline) -> io ()) -> r) -> r
withGraphicsPipelines :: Device
-> PipelineCache
-> ("createInfos"
    ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io (Result, "pipelines" ::: Vector Pipeline)
    -> ((Result, "pipelines" ::: Vector Pipeline) -> io ()) -> r)
-> r
withGraphicsPipelines device :: Device
device pipelineCache :: PipelineCache
pipelineCache pCreateInfos :: "createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo)
pCreateInfos pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io (Result, "pipelines" ::: Vector Pipeline)
-> ((Result, "pipelines" ::: Vector Pipeline) -> io ()) -> r
b =
  io (Result, "pipelines" ::: Vector Pipeline)
-> ((Result, "pipelines" ::: Vector Pipeline) -> io ()) -> r
b (Device
-> PipelineCache
-> ("createInfos"
    ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall (io :: * -> *).
MonadIO io =>
Device
-> PipelineCache
-> ("createInfos"
    ::: Vector (SomeStruct GraphicsPipelineCreateInfo))
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io (Result, "pipelines" ::: Vector Pipeline)
createGraphicsPipelines Device
device PipelineCache
pipelineCache "createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo)
pCreateInfos "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(_, o1 :: "pipelines" ::: Vector Pipeline
o1) -> (Pipeline -> io ()) -> ("pipelines" ::: Vector Pipeline) -> io ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (\o1Elem :: Pipeline
o1Elem -> Device
-> Pipeline -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> Pipeline -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyPipeline Device
device Pipeline
o1Elem "allocator" ::: Maybe AllocationCallbacks
pAllocator) "pipelines" ::: Vector Pipeline
o1)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateComputePipelines
  :: FunPtr (Ptr Device_T -> PipelineCache -> Word32 -> Ptr (SomeStruct ComputePipelineCreateInfo) -> Ptr AllocationCallbacks -> Ptr Pipeline -> IO Result) -> Ptr Device_T -> PipelineCache -> Word32 -> Ptr (SomeStruct ComputePipelineCreateInfo) -> Ptr AllocationCallbacks -> Ptr Pipeline -> IO Result

-- | vkCreateComputePipelines - Creates a new compute pipeline object
--
-- == Valid Usage
--
-- -   If the @flags@ member of any element of @pCreateInfos@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and the @basePipelineIndex@ member of that same element is not
--     @-1@, @basePipelineIndex@ /must/ be less than the index into
--     @pCreateInfos@ that corresponds to that element
--
-- -   If the @flags@ member of any element of @pCreateInfos@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, the base pipeline /must/ have been created with the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT'
--     flag set
--
-- -   If @pipelineCache@ was created with
--     'Vulkan.Core10.Enums.PipelineCacheCreateFlagBits.PIPELINE_CACHE_CREATE_EXTERNALLY_SYNCHRONIZED_BIT_EXT',
--     host access to @pipelineCache@ /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-threadingbehavior externally synchronized>
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @pipelineCache@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @pipelineCache@ /must/ be a valid
--     'Vulkan.Core10.Handles.PipelineCache' handle
--
-- -   @pCreateInfos@ /must/ be a valid pointer to an array of
--     @createInfoCount@ valid 'ComputePipelineCreateInfo' structures
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pPipelines@ /must/ be a valid pointer to an array of
--     @createInfoCount@ 'Vulkan.Core10.Handles.Pipeline' handles
--
-- -   @createInfoCount@ /must/ be greater than @0@
--
-- -   If @pipelineCache@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.PIPELINE_COMPILE_REQUIRED_EXT'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_INVALID_SHADER_NV'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'ComputePipelineCreateInfo', 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Core10.Handles.Pipeline', 'Vulkan.Core10.Handles.PipelineCache'
createComputePipelines :: forall io
                        . (MonadIO io)
                       => -- | @device@ is the logical device that creates the compute pipelines.
                          Device
                       -> -- | @pipelineCache@ is either 'Vulkan.Core10.APIConstants.NULL_HANDLE',
                          -- indicating that pipeline caching is disabled; or the handle of a valid
                          -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipelines-cache pipeline cache>
                          -- object, in which case use of that cache is enabled for the duration of
                          -- the command.
                          PipelineCache
                       -> -- | @pCreateInfos@ is a pointer to an array of 'ComputePipelineCreateInfo'
                          -- structures.
                          ("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo))
                       -> -- | @pAllocator@ controls host memory allocation as described in the
                          -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                          -- chapter.
                          ("allocator" ::: Maybe AllocationCallbacks)
                       -> io (Result, ("pipelines" ::: Vector Pipeline))
createComputePipelines :: Device
-> PipelineCache
-> ("createInfos"
    ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io (Result, "pipelines" ::: Vector Pipeline)
createComputePipelines device :: Device
device pipelineCache :: PipelineCache
pipelineCache createInfos :: "createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo)
createInfos allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO (Result, "pipelines" ::: Vector Pipeline)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "pipelines" ::: Vector Pipeline)
 -> io (Result, "pipelines" ::: Vector Pipeline))
-> (ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      (Result, "pipelines" ::: Vector Pipeline)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "pipelines" ::: Vector Pipeline)
  IO
  (Result, "pipelines" ::: Vector Pipeline)
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "pipelines" ::: Vector Pipeline)
   IO
   (Result, "pipelines" ::: Vector Pipeline)
 -> io (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateComputePipelinesPtr :: FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
vkCreateComputePipelinesPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("createInfoCount" ::: Word32)
      -> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pPipelines" ::: Ptr Pipeline)
      -> IO Result)
pVkCreateComputePipelines (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
vkCreateComputePipelinesPtr FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("createInfoCount" ::: Word32)
      -> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pPipelines" ::: Ptr Pipeline)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkCreateComputePipelines is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateComputePipelines' :: Ptr Device_T
-> PipelineCache
-> ("createInfoCount" ::: Word32)
-> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelines" ::: Ptr Pipeline)
-> IO Result
vkCreateComputePipelines' = FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
-> Ptr Device_T
-> PipelineCache
-> ("createInfoCount" ::: Word32)
-> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelines" ::: Ptr Pipeline)
-> IO Result
mkVkCreateComputePipelines FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("createInfoCount" ::: Word32)
   -> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
vkCreateComputePipelinesPtr
  Ptr (ComputePipelineCreateInfo Any)
pPCreateInfos <- ((Ptr (ComputePipelineCreateInfo Any)
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Ptr (ComputePipelineCreateInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (ComputePipelineCreateInfo Any)
   -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      (Ptr (ComputePipelineCreateInfo Any)))
-> ((Ptr (ComputePipelineCreateInfo Any)
     -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Ptr (ComputePipelineCreateInfo Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr (ComputePipelineCreateInfo Any)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(ComputePipelineCreateInfo _) ((("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo)
createInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 96) 8
  (Int
 -> SomeStruct ComputePipelineCreateInfo
 -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> ("createInfos"
    ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct ComputePipelineCreateInfo
e -> ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall a b. (a -> b) -> a -> b
$ ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
-> SomeStruct ComputePipelineCreateInfo
-> IO (Result, "pipelines" ::: Vector Pipeline)
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (ComputePipelineCreateInfo Any)
-> "pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (ComputePipelineCreateInfo Any)
pPCreateInfos Ptr (ComputePipelineCreateInfo Any)
-> Int -> Ptr (ComputePipelineCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (96 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (ComputePipelineCreateInfo _))) (SomeStruct ComputePipelineCreateInfo
e) (IO (Result, "pipelines" ::: Vector Pipeline)
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> (() -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
-> () -> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ ())) ("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo)
createInfos)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks)
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks)
     -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pPipelines" ::: Ptr Pipeline
pPPipelines <- ((("pPipelines" ::: Ptr Pipeline)
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pPipelines" ::: Ptr Pipeline)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPipelines" ::: Ptr Pipeline)
   -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      ("pPipelines" ::: Ptr Pipeline))
-> ((("pPipelines" ::: Ptr Pipeline)
     -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pPipelines" ::: Ptr Pipeline)
forall a b. (a -> b) -> a -> b
$ IO ("pPipelines" ::: Ptr Pipeline)
-> (("pPipelines" ::: Ptr Pipeline) -> IO ())
-> (("pPipelines" ::: Ptr Pipeline)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPipelines" ::: Ptr Pipeline)
forall a. Int -> IO (Ptr a)
callocBytes @Pipeline ((("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo))
 -> Int)
-> ("createInfos"
    ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> Int
forall a b. (a -> b) -> a -> b
$ ("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo)
createInfos)) :: Word32))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8)) ("pPipelines" ::: Ptr Pipeline) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT (Result, "pipelines" ::: Vector Pipeline) IO Result)
-> IO Result
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> PipelineCache
-> ("createInfoCount" ::: Word32)
-> ("pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelines" ::: Ptr Pipeline)
-> IO Result
vkCreateComputePipelines' (Device -> Ptr Device_T
deviceHandle (Device
device)) (PipelineCache
pipelineCache) ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo))
 -> Int)
-> ("createInfos"
    ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> Int
forall a b. (a -> b) -> a -> b
$ ("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo)
createInfos)) :: Word32)) (Ptr (ComputePipelineCreateInfo Any)
-> "pCreateInfos" ::: Ptr (SomeStruct ComputePipelineCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (ComputePipelineCreateInfo Any)
pPCreateInfos)) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pPipelines" ::: Ptr Pipeline
pPPipelines)
  IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  "pipelines" ::: Vector Pipeline
pPipelines <- IO ("pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pipelines" ::: Vector Pipeline)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("pipelines" ::: Vector Pipeline)
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      ("pipelines" ::: Vector Pipeline))
-> IO ("pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> IO Pipeline) -> IO ("pipelines" ::: Vector Pipeline)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo))
 -> Int)
-> ("createInfos"
    ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> Int
forall a b. (a -> b) -> a -> b
$ ("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo)
createInfos)) :: Word32))) (\i :: Int
i -> ("pPipelines" ::: Ptr Pipeline) -> IO Pipeline
forall a. Storable a => Ptr a -> IO a
peek @Pipeline (("pPipelines" ::: Ptr Pipeline
pPPipelines ("pPipelines" ::: Ptr Pipeline)
-> Int -> "pPipelines" ::: Ptr Pipeline
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Pipeline)))
  (Result, "pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "pipelines" ::: Vector Pipeline)
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      (Result, "pipelines" ::: Vector Pipeline))
-> (Result, "pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ (Result
r, "pipelines" ::: Vector Pipeline
pPipelines)

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createComputePipelines' and 'destroyPipeline'
--
-- To ensure that 'destroyPipeline' is always called: pass
-- 'Control.Exception.bracket' (or the allocate function from your
-- favourite resource management library) as the first argument.
-- To just extract the pair pass '(,)' as the first argument.
--
withComputePipelines :: forall io r . MonadIO io => Device -> PipelineCache -> Vector (SomeStruct ComputePipelineCreateInfo) -> Maybe AllocationCallbacks -> (io (Result, Vector Pipeline) -> ((Result, Vector Pipeline) -> io ()) -> r) -> r
withComputePipelines :: Device
-> PipelineCache
-> ("createInfos"
    ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io (Result, "pipelines" ::: Vector Pipeline)
    -> ((Result, "pipelines" ::: Vector Pipeline) -> io ()) -> r)
-> r
withComputePipelines device :: Device
device pipelineCache :: PipelineCache
pipelineCache pCreateInfos :: "createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo)
pCreateInfos pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io (Result, "pipelines" ::: Vector Pipeline)
-> ((Result, "pipelines" ::: Vector Pipeline) -> io ()) -> r
b =
  io (Result, "pipelines" ::: Vector Pipeline)
-> ((Result, "pipelines" ::: Vector Pipeline) -> io ()) -> r
b (Device
-> PipelineCache
-> ("createInfos"
    ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall (io :: * -> *).
MonadIO io =>
Device
-> PipelineCache
-> ("createInfos"
    ::: Vector (SomeStruct ComputePipelineCreateInfo))
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io (Result, "pipelines" ::: Vector Pipeline)
createComputePipelines Device
device PipelineCache
pipelineCache "createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo)
pCreateInfos "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(_, o1 :: "pipelines" ::: Vector Pipeline
o1) -> (Pipeline -> io ()) -> ("pipelines" ::: Vector Pipeline) -> io ()
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
(a -> f b) -> t a -> f ()
traverse_ (\o1Elem :: Pipeline
o1Elem -> Device
-> Pipeline -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> Pipeline -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyPipeline Device
device Pipeline
o1Elem "allocator" ::: Maybe AllocationCallbacks
pAllocator) "pipelines" ::: Vector Pipeline
o1)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDestroyPipeline
  :: FunPtr (Ptr Device_T -> Pipeline -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> Pipeline -> Ptr AllocationCallbacks -> IO ()

-- | vkDestroyPipeline - Destroy a pipeline object
--
-- == Valid Usage
--
-- -   All submitted commands that refer to @pipeline@ /must/ have
--     completed execution
--
-- -   If 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @pipeline@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   If no 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @pipeline@ was created, @pAllocator@ /must/ be @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @pipeline@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @pipeline@ /must/ be a valid 'Vulkan.Core10.Handles.Pipeline' handle
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   If @pipeline@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Host Synchronization
--
-- -   Host access to @pipeline@ /must/ be externally synchronized
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Pipeline'
destroyPipeline :: forall io
                 . (MonadIO io)
                => -- | @device@ is the logical device that destroys the pipeline.
                   Device
                -> -- | @pipeline@ is the handle of the pipeline to destroy.
                   Pipeline
                -> -- | @pAllocator@ controls host memory allocation as described in the
                   -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                   -- chapter.
                   ("allocator" ::: Maybe AllocationCallbacks)
                -> io ()
destroyPipeline :: Device
-> Pipeline -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyPipeline device :: Device
device pipeline :: Pipeline
pipeline allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDestroyPipelinePtr :: FunPtr
  (Ptr Device_T
   -> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyPipelinePtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
pVkDestroyPipeline (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyPipelinePtr FunPtr
  (Ptr Device_T
   -> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> FunPtr
     (Ptr Device_T
      -> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkDestroyPipeline is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyPipeline' :: Ptr Device_T
-> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyPipeline' = FunPtr
  (Ptr Device_T
   -> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Ptr Device_T
-> Pipeline
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyPipeline FunPtr
  (Ptr Device_T
   -> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyPipelinePtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> Pipeline -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyPipeline' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Pipeline
pipeline) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkViewport - Structure specifying a viewport
--
-- = Description
--
-- The framebuffer depth coordinate @z@f /may/ be represented using either
-- a fixed-point or floating-point representation. However, a
-- floating-point representation /must/ be used if the depth\/stencil
-- attachment has a floating-point depth component. If an m-bit fixed-point
-- representation is used, we assume that it represents each value
-- \(\frac{k}{2^m - 1}\), where k ∈ { 0, 1, …​, 2m-1 }, as k (e.g. 1.0 is
-- represented in binary as a string of all ones).
--
-- The viewport parameters shown in the above equations are found from
-- these values as
--
-- -   ox = @x@ + @width@ \/ 2
--
-- -   oy = @y@ + @height@ \/ 2
--
-- -   oz = @minDepth@
--
-- -   px = @width@
--
-- -   py = @height@
--
-- -   pz = @maxDepth@ - @minDepth@.
--
-- If a render pass transform is enabled, the values (px,py) and (ox, oy)
-- defining the viewport are transformed as described in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vertexpostproc-renderpass-transform render pass transform>
-- before participating in the viewport transform.
--
-- The application /can/ specify a negative term for @height@, which has
-- the effect of negating the y coordinate in clip space before performing
-- the transform. When using a negative @height@, the application /should/
-- also adjust the @y@ value to point to the lower left corner of the
-- viewport instead of the upper left corner. Using the negative @height@
-- allows the application to avoid having to negate the y component of the
-- @Position@ output from the last vertex processing stage in shaders that
-- also target other graphics APIs.
--
-- The width and height of the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxViewportDimensions implementation-dependent maximum viewport dimensions>
-- /must/ be greater than or equal to the width and height of the largest
-- image which /can/ be created and attached to a framebuffer.
--
-- The floating-point viewport bounds are represented with an
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-viewportSubPixelBits implementation-dependent precision>.
--
-- == Valid Usage
--
-- -   @width@ /must/ be greater than @0.0@
--
-- -   @width@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewportDimensions@[0]
--
-- -   The absolute value of @height@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewportDimensions@[1]
--
-- -   @x@ /must/ be greater than or equal to @viewportBoundsRange@[0]
--
-- -   (@x@ + @width@) /must/ be less than or equal to
--     @viewportBoundsRange@[1]
--
-- -   @y@ /must/ be greater than or equal to @viewportBoundsRange@[0]
--
-- -   @y@ /must/ be less than or equal to @viewportBoundsRange@[1]
--
-- -   (@y@ + @height@) /must/ be greater than or equal to
--     @viewportBoundsRange@[0]
--
-- -   (@y@ + @height@) /must/ be less than or equal to
--     @viewportBoundsRange@[1]
--
-- -   Unless @VK_EXT_depth_range_unrestricted@ extension is enabled
--     @minDepth@ /must/ be between @0.0@ and @1.0@, inclusive
--
-- -   Unless @VK_EXT_depth_range_unrestricted@ extension is enabled
--     @maxDepth@ /must/ be between @0.0@ and @1.0@, inclusive
--
-- = See Also
--
-- 'PipelineViewportStateCreateInfo',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetViewport',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT'
data Viewport = Viewport
  { -- | @x@ and @y@ are the viewport’s upper left corner (x,y).
    Viewport -> Float
x :: Float
  , -- No documentation found for Nested "VkViewport" "y"
    Viewport -> Float
y :: Float
  , -- | @width@ and @height@ are the viewport’s width and height, respectively.
    Viewport -> Float
width :: Float
  , -- No documentation found for Nested "VkViewport" "height"
    Viewport -> Float
height :: Float
  , -- | @minDepth@ and @maxDepth@ are the depth range for the viewport. It is
    -- valid for @minDepth@ to be greater than or equal to @maxDepth@.
    Viewport -> Float
minDepth :: Float
  , -- No documentation found for Nested "VkViewport" "maxDepth"
    Viewport -> Float
maxDepth :: Float
  }
  deriving (Typeable, Viewport -> Viewport -> Bool
(Viewport -> Viewport -> Bool)
-> (Viewport -> Viewport -> Bool) -> Eq Viewport
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Viewport -> Viewport -> Bool
$c/= :: Viewport -> Viewport -> Bool
== :: Viewport -> Viewport -> Bool
$c== :: Viewport -> Viewport -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (Viewport)
#endif
deriving instance Show Viewport

instance ToCStruct Viewport where
  withCStruct :: Viewport -> (Ptr Viewport -> IO b) -> IO b
withCStruct x :: Viewport
x f :: Ptr Viewport -> IO b
f = Int -> Int -> (Ptr Viewport -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 4 ((Ptr Viewport -> IO b) -> IO b) -> (Ptr Viewport -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr Viewport
p -> Ptr Viewport -> Viewport -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Viewport
p Viewport
x (Ptr Viewport -> IO b
f Ptr Viewport
p)
  pokeCStruct :: Ptr Viewport -> Viewport -> IO b -> IO b
pokeCStruct p :: Ptr Viewport
p Viewport{..} f :: IO b
f = do
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
x))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
y))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
width))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
height))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
minDepth))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxDepth))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr Viewport -> IO b -> IO b
pokeZeroCStruct p :: Ptr Viewport
p f :: IO b
f = do
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct Viewport where
  peekCStruct :: Ptr Viewport -> IO Viewport
peekCStruct p :: Ptr Viewport
p = do
    CFloat
x <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat))
    CFloat
y <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat))
    CFloat
width <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat))
    CFloat
height <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat))
    CFloat
minDepth <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CFloat))
    CFloat
maxDepth <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr Viewport
p Ptr Viewport -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr CFloat))
    Viewport -> IO Viewport
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Viewport -> IO Viewport) -> Viewport -> IO Viewport
forall a b. (a -> b) -> a -> b
$ Float -> Float -> Float -> Float -> Float -> Float -> Viewport
Viewport
             ((\(CFloat a :: Float
a) -> Float
a) CFloat
x) ((\(CFloat a :: Float
a) -> Float
a) CFloat
y) ((\(CFloat a :: Float
a) -> Float
a) CFloat
width) ((\(CFloat a :: Float
a) -> Float
a) CFloat
height) ((\(CFloat a :: Float
a) -> Float
a) CFloat
minDepth) ((\(CFloat a :: Float
a) -> Float
a) CFloat
maxDepth)

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

instance Zero Viewport where
  zero :: Viewport
zero = Float -> Float -> Float -> Float -> Float -> Float -> Viewport
Viewport
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero


-- | VkSpecializationMapEntry - Structure specifying a specialization map
-- entry
--
-- = Description
--
-- If a @constantID@ value is not a specialization constant ID used in the
-- shader, that map entry does not affect the behavior of the pipeline.
--
-- == Valid Usage
--
-- -   For a @constantID@ specialization constant declared in a shader,
--     @size@ /must/ match the byte size of the @constantID@. If the
--     specialization constant is of type @boolean@, @size@ /must/ be the
--     byte size of 'Vulkan.Core10.FundamentalTypes.Bool32'
--
-- = See Also
--
-- 'SpecializationInfo'
data SpecializationMapEntry = SpecializationMapEntry
  { -- | @constantID@ is the ID of the specialization constant in SPIR-V.
    SpecializationMapEntry -> "createInfoCount" ::: Word32
constantID :: Word32
  , -- | @offset@ is the byte offset of the specialization constant value within
    -- the supplied data buffer.
    SpecializationMapEntry -> "createInfoCount" ::: Word32
offset :: Word32
  , -- | @size@ is the byte size of the specialization constant value within the
    -- supplied data buffer.
    SpecializationMapEntry -> Word64
size :: Word64
  }
  deriving (Typeable, SpecializationMapEntry -> SpecializationMapEntry -> Bool
(SpecializationMapEntry -> SpecializationMapEntry -> Bool)
-> (SpecializationMapEntry -> SpecializationMapEntry -> Bool)
-> Eq SpecializationMapEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SpecializationMapEntry -> SpecializationMapEntry -> Bool
$c/= :: SpecializationMapEntry -> SpecializationMapEntry -> Bool
== :: SpecializationMapEntry -> SpecializationMapEntry -> Bool
$c== :: SpecializationMapEntry -> SpecializationMapEntry -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SpecializationMapEntry)
#endif
deriving instance Show SpecializationMapEntry

instance ToCStruct SpecializationMapEntry where
  withCStruct :: SpecializationMapEntry
-> (Ptr SpecializationMapEntry -> IO b) -> IO b
withCStruct x :: SpecializationMapEntry
x f :: Ptr SpecializationMapEntry -> IO b
f = Int -> Int -> (Ptr SpecializationMapEntry -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 8 ((Ptr SpecializationMapEntry -> IO b) -> IO b)
-> (Ptr SpecializationMapEntry -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SpecializationMapEntry
p -> Ptr SpecializationMapEntry
-> SpecializationMapEntry -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SpecializationMapEntry
p SpecializationMapEntry
x (Ptr SpecializationMapEntry -> IO b
f Ptr SpecializationMapEntry
p)
  pokeCStruct :: Ptr SpecializationMapEntry
-> SpecializationMapEntry -> IO b -> IO b
pokeCStruct p :: Ptr SpecializationMapEntry
p SpecializationMapEntry{..} f :: IO b
f = do
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationMapEntry
p Ptr SpecializationMapEntry
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("createInfoCount" ::: Word32
constantID)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationMapEntry
p Ptr SpecializationMapEntry
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("createInfoCount" ::: Word32
offset)
    Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationMapEntry
p Ptr SpecializationMapEntry -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
size))
    IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr SpecializationMapEntry -> IO b -> IO b
pokeZeroCStruct p :: Ptr SpecializationMapEntry
p f :: IO b
f = do
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationMapEntry
p Ptr SpecializationMapEntry
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationMapEntry
p Ptr SpecializationMapEntry
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationMapEntry
p Ptr SpecializationMapEntry -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct SpecializationMapEntry where
  peekCStruct :: Ptr SpecializationMapEntry -> IO SpecializationMapEntry
peekCStruct p :: Ptr SpecializationMapEntry
p = do
    "createInfoCount" ::: Word32
constantID <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SpecializationMapEntry
p Ptr SpecializationMapEntry
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    "createInfoCount" ::: Word32
offset <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SpecializationMapEntry
p Ptr SpecializationMapEntry
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    CSize
size <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr SpecializationMapEntry
p Ptr SpecializationMapEntry -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CSize))
    SpecializationMapEntry -> IO SpecializationMapEntry
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SpecializationMapEntry -> IO SpecializationMapEntry)
-> SpecializationMapEntry -> IO SpecializationMapEntry
forall a b. (a -> b) -> a -> b
$ ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> Word64
-> SpecializationMapEntry
SpecializationMapEntry
             "createInfoCount" ::: Word32
constantID "createInfoCount" ::: Word32
offset ((\(CSize a :: Word64
a) -> Word64
a) CSize
size)

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

instance Zero SpecializationMapEntry where
  zero :: SpecializationMapEntry
zero = ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> Word64
-> SpecializationMapEntry
SpecializationMapEntry
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero


-- | VkSpecializationInfo - Structure specifying specialization info
--
-- = Description
--
-- @pMapEntries@ is a pointer to a 'SpecializationMapEntry' structure.
--
-- == Valid Usage
--
-- -   The @offset@ member of each element of @pMapEntries@ /must/ be less
--     than @dataSize@
--
-- -   The @size@ member of each element of @pMapEntries@ /must/ be less
--     than or equal to @dataSize@ minus @offset@
--
-- == Valid Usage (Implicit)
--
-- -   If @mapEntryCount@ is not @0@, @pMapEntries@ /must/ be a valid
--     pointer to an array of @mapEntryCount@ valid
--     'SpecializationMapEntry' structures
--
-- -   If @dataSize@ is not @0@, @pData@ /must/ be a valid pointer to an
--     array of @dataSize@ bytes
--
-- = See Also
--
-- 'PipelineShaderStageCreateInfo', 'SpecializationMapEntry'
data SpecializationInfo = SpecializationInfo
  { -- | @pMapEntries@ is a pointer to an array of 'SpecializationMapEntry'
    -- structures which map constant IDs to offsets in @pData@.
    SpecializationInfo -> Vector SpecializationMapEntry
mapEntries :: Vector SpecializationMapEntry
  , -- | @dataSize@ is the byte size of the @pData@ buffer.
    SpecializationInfo -> Word64
dataSize :: Word64
  , -- | @pData@ contains the actual constant values to specialize with.
    SpecializationInfo -> Ptr ()
data' :: Ptr ()
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SpecializationInfo)
#endif
deriving instance Show SpecializationInfo

instance ToCStruct SpecializationInfo where
  withCStruct :: SpecializationInfo -> (Ptr SpecializationInfo -> IO b) -> IO b
withCStruct x :: SpecializationInfo
x f :: Ptr SpecializationInfo -> IO b
f = Int -> Int -> (Ptr SpecializationInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr SpecializationInfo -> IO b) -> IO b)
-> (Ptr SpecializationInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SpecializationInfo
p -> Ptr SpecializationInfo -> SpecializationInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SpecializationInfo
p SpecializationInfo
x (Ptr SpecializationInfo -> IO b
f Ptr SpecializationInfo
p)
  pokeCStruct :: Ptr SpecializationInfo -> SpecializationInfo -> IO b -> IO b
pokeCStruct p :: Ptr SpecializationInfo
p SpecializationInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SpecializationMapEntry -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SpecializationMapEntry -> Int)
-> Vector SpecializationMapEntry -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SpecializationMapEntry
mapEntries)) :: Word32))
    Ptr SpecializationMapEntry
pPMapEntries' <- ((Ptr SpecializationMapEntry -> IO b) -> IO b)
-> ContT b IO (Ptr SpecializationMapEntry)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SpecializationMapEntry -> IO b) -> IO b)
 -> ContT b IO (Ptr SpecializationMapEntry))
-> ((Ptr SpecializationMapEntry -> IO b) -> IO b)
-> ContT b IO (Ptr SpecializationMapEntry)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SpecializationMapEntry -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SpecializationMapEntry ((Vector SpecializationMapEntry -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SpecializationMapEntry
mapEntries)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 8
    (Int -> SpecializationMapEntry -> ContT b IO ())
-> Vector SpecializationMapEntry -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SpecializationMapEntry
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SpecializationMapEntry
-> SpecializationMapEntry -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SpecializationMapEntry
pPMapEntries' Ptr SpecializationMapEntry -> Int -> Ptr SpecializationMapEntry
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SpecializationMapEntry) (SpecializationMapEntry
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SpecializationMapEntry
mapEntries)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SpecializationMapEntry)
-> Ptr SpecializationMapEntry -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr (Ptr SpecializationMapEntry)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr SpecializationMapEntry))) (Ptr SpecializationMapEntry
pPMapEntries')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
dataSize))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr ()))) (Ptr ()
data')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr SpecializationInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr SpecializationInfo
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    Ptr SpecializationMapEntry
pPMapEntries' <- ((Ptr SpecializationMapEntry -> IO b) -> IO b)
-> ContT b IO (Ptr SpecializationMapEntry)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SpecializationMapEntry -> IO b) -> IO b)
 -> ContT b IO (Ptr SpecializationMapEntry))
-> ((Ptr SpecializationMapEntry -> IO b) -> IO b)
-> ContT b IO (Ptr SpecializationMapEntry)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SpecializationMapEntry -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SpecializationMapEntry ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 8
    (Int -> SpecializationMapEntry -> ContT b IO ())
-> Vector SpecializationMapEntry -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SpecializationMapEntry
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SpecializationMapEntry
-> SpecializationMapEntry -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SpecializationMapEntry
pPMapEntries' Ptr SpecializationMapEntry -> Int -> Ptr SpecializationMapEntry
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SpecializationMapEntry) (SpecializationMapEntry
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector SpecializationMapEntry
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SpecializationMapEntry)
-> Ptr SpecializationMapEntry -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr (Ptr SpecializationMapEntry)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr SpecializationMapEntry))) (Ptr SpecializationMapEntry
pPMapEntries')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr ()))) (Ptr ()
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct SpecializationInfo where
  peekCStruct :: Ptr SpecializationInfo -> IO SpecializationInfo
peekCStruct p :: Ptr SpecializationInfo
p = do
    "createInfoCount" ::: Word32
mapEntryCount <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    Ptr SpecializationMapEntry
pMapEntries <- Ptr (Ptr SpecializationMapEntry) -> IO (Ptr SpecializationMapEntry)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SpecializationMapEntry) ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr (Ptr SpecializationMapEntry)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr SpecializationMapEntry)))
    Vector SpecializationMapEntry
pMapEntries' <- Int
-> (Int -> IO SpecializationMapEntry)
-> IO (Vector SpecializationMapEntry)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "createInfoCount" ::: Word32
mapEntryCount) (\i :: Int
i -> Ptr SpecializationMapEntry -> IO SpecializationMapEntry
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SpecializationMapEntry ((Ptr SpecializationMapEntry
pMapEntries Ptr SpecializationMapEntry -> Int -> Ptr SpecializationMapEntry
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SpecializationMapEntry)))
    CSize
dataSize <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CSize))
    Ptr ()
pData <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr SpecializationInfo
p Ptr SpecializationInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr ())))
    SpecializationInfo -> IO SpecializationInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SpecializationInfo -> IO SpecializationInfo)
-> SpecializationInfo -> IO SpecializationInfo
forall a b. (a -> b) -> a -> b
$ Vector SpecializationMapEntry
-> Word64 -> Ptr () -> SpecializationInfo
SpecializationInfo
             Vector SpecializationMapEntry
pMapEntries' ((\(CSize a :: Word64
a) -> Word64
a) CSize
dataSize) Ptr ()
pData

instance Zero SpecializationInfo where
  zero :: SpecializationInfo
zero = Vector SpecializationMapEntry
-> Word64 -> Ptr () -> SpecializationInfo
SpecializationInfo
           Vector SpecializationMapEntry
forall a. Monoid a => a
mempty
           Word64
forall a. Zero a => a
zero
           Ptr ()
forall a. Zero a => a
zero


-- | VkPipelineShaderStageCreateInfo - Structure specifying parameters of a
-- newly created pipeline shader stage
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @stage@ /must/ not be
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @stage@ /must/ not be
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT'
--     or
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shader>
--     feature is not enabled, @stage@ /must/ not be
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shader>
--     feature is not enabled, @stage@ /must/ not be
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_NV'
--
-- -   @stage@ /must/ not be
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_ALL_GRAPHICS',
--     or 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_ALL'
--
-- -   @pName@ /must/ be the name of an @OpEntryPoint@ in @module@ with an
--     execution model that matches @stage@
--
-- -   If the identified entry point includes any variable in its interface
--     that is declared with the @ClipDistance@ @BuiltIn@ decoration, that
--     variable /must/ not have an array size greater than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxClipDistances@
--
-- -   If the identified entry point includes any variable in its interface
--     that is declared with the @CullDistance@ @BuiltIn@ decoration, that
--     variable /must/ not have an array size greater than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxCullDistances@
--
-- -   If the identified entry point includes any variables in its
--     interface that are declared with the @ClipDistance@ or
--     @CullDistance@ @BuiltIn@ decoration, those variables /must/ not have
--     array sizes which sum to more than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxCombinedClipAndCullDistances@
--
-- -   If the identified entry point includes any variable in its interface
--     that is declared with the
--     'Vulkan.Core10.FundamentalTypes.SampleMask' @BuiltIn@ decoration,
--     that variable /must/ not have an array size greater than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxSampleMaskWords@
--
-- -   If @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT',
--     the identified entry point /must/ not include any input variable in
--     its interface that is decorated with @CullDistance@
--
-- -   If @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT'
--     or
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT',
--     and the identified entry point has an @OpExecutionMode@ instruction
--     that specifies a patch size with @OutputVertices@, the patch size
--     /must/ be greater than @0@ and less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxTessellationPatchSize@
--
-- -   If @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT',
--     the identified entry point /must/ have an @OpExecutionMode@
--     instruction that specifies a maximum output vertex count that is
--     greater than @0@ and less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxGeometryOutputVertices@
--
-- -   If @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT',
--     the identified entry point /must/ have an @OpExecutionMode@
--     instruction that specifies an invocation count that is greater than
--     @0@ and less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxGeometryShaderInvocations@
--
-- -   If @stage@ is a vertex processing stage, and the identified entry
--     point writes to @Layer@ for any primitive, it /must/ write the same
--     value to @Layer@ for all vertices of a given primitive
--
-- -   If @stage@ is a vertex processing stage, and the identified entry
--     point writes to @ViewportIndex@ for any primitive, it /must/ write
--     the same value to @ViewportIndex@ for all vertices of a given
--     primitive
--
-- -   If @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT',
--     the identified entry point /must/ not include any output variables
--     in its interface decorated with @CullDistance@
--
-- -   If @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT',
--     and the identified entry point writes to @FragDepth@ in any
--     execution path, it /must/ write to @FragDepth@ in all execution
--     paths
--
-- -   If @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_FRAGMENT_BIT',
--     and the identified entry point writes to @FragStencilRefEXT@ in any
--     execution path, it /must/ write to @FragStencilRefEXT@ in all
--     execution paths
--
-- -   If @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_NV',
--     the identified entry point /must/ have an @OpExecutionMode@
--     instruction that specifies a maximum output vertex count,
--     @OutputVertices@, that is greater than @0@ and less than or equal to
--     'Vulkan.Extensions.VK_NV_mesh_shader.PhysicalDeviceMeshShaderPropertiesNV'::@maxMeshOutputVertices@
--
-- -   If @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_NV',
--     the identified entry point /must/ have an @OpExecutionMode@
--     instruction that specifies a maximum output primitive count,
--     @OutputPrimitivesNV@, that is greater than @0@ and less than or
--     equal to
--     'Vulkan.Extensions.VK_NV_mesh_shader.PhysicalDeviceMeshShaderPropertiesNV'::@maxMeshOutputPrimitives@
--
-- -   If @flags@ has the
--     'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_ALLOW_VARYING_SUBGROUP_SIZE_BIT_EXT'
--     flag set, the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-subgroupSizeControl subgroupSizeControl>
--     feature /must/ be enabled
--
-- -   If @flags@ has the
--     'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_REQUIRE_FULL_SUBGROUPS_BIT_EXT'
--     flag set, the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-computeFullSubgroups computeFullSubgroups>
--     feature /must/ be enabled
--
-- -   If a
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT'
--     structure is included in the @pNext@ chain, @flags@ /must/ not have
--     the
--     'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_ALLOW_VARYING_SUBGROUP_SIZE_BIT_EXT'
--     flag set
--
-- -   If a
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT'
--     structure is included in the @pNext@ chain, the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-subgroupSizeControl subgroupSizeControl>
--     feature /must/ be enabled, and @stage@ /must/ be a valid bit
--     specified in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-required-subgroup-size-stages requiredSubgroupSizeStages>
--
-- -   If a
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT'
--     structure is included in the @pNext@ chain and @stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_COMPUTE_BIT',
--     the local workgroup size of the shader /must/ be less than or equal
--     to the product of
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT'::@requiredSubgroupSize@
--     and
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-max-subgroups-per-workgroup maxComputeWorkgroupSubgroups>
--
-- -   If a
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT'
--     structure is included in the @pNext@ chain, and @flags@ has the
--     'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_REQUIRE_FULL_SUBGROUPS_BIT_EXT'
--     flag set, the local workgroup size in the X dimension of the
--     pipeline /must/ be a multiple of
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT'::@requiredSubgroupSize@
--
-- -   If @flags@ has both the
--     'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_REQUIRE_FULL_SUBGROUPS_BIT_EXT'
--     and
--     'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_ALLOW_VARYING_SUBGROUP_SIZE_BIT_EXT'
--     flags set, the local workgroup size in the X dimension of the
--     pipeline /must/ be a multiple of
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-max-subgroup-size maxSubgroupSize>
--
-- -   If @flags@ has the
--     'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_REQUIRE_FULL_SUBGROUPS_BIT_EXT'
--     flag set and @flags@ does not have the
--     'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PIPELINE_SHADER_STAGE_CREATE_ALLOW_VARYING_SUBGROUP_SIZE_BIT_EXT'
--     flag set and no
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT'
--     structure is included in the @pNext@ chain, the local workgroup size
--     in the X dimension of the pipeline /must/ be a multiple of
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-subgroup-size subgroupSize>
--
-- -   The SPIR-V code that was used to create @module@ /must/ be valid as
--     described by the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#spirv-spec Khronos SPIR-V Specification>
--     after applying the specializations provided in
--     @pSpecializationInfo@, if any, and then converting all
--     specialization constants into fixed constants.
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_CREATE_INFO'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PipelineShaderStageCreateFlagBits'
--     values
--
-- -   @stage@ /must/ be a valid
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits' value
--
-- -   @module@ /must/ be a valid 'Vulkan.Core10.Handles.ShaderModule'
--     handle
--
-- -   @pName@ /must/ be a null-terminated UTF-8 string
--
-- -   If @pSpecializationInfo@ is not @NULL@, @pSpecializationInfo@ /must/
--     be a valid pointer to a valid 'SpecializationInfo' structure
--
-- = See Also
--
-- 'ComputePipelineCreateInfo', 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.GraphicsShaderGroupCreateInfoNV',
-- 'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PipelineShaderStageCreateFlags',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.RayTracingPipelineCreateInfoKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.RayTracingPipelineCreateInfoNV',
-- 'Vulkan.Core10.Handles.ShaderModule',
-- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits',
-- 'SpecializationInfo', 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineShaderStageCreateInfo (es :: [Type]) = PipelineShaderStageCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PipelineShaderStageCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits.PipelineShaderStageCreateFlagBits'
    -- specifying how the pipeline shader stage will be generated.
    PipelineShaderStageCreateInfo es -> PipelineShaderStageCreateFlags
flags :: PipelineShaderStageCreateFlags
  , -- | @stage@ is a
    -- 'Vulkan.Core10.Enums.ShaderStageFlagBits.ShaderStageFlagBits' value
    -- specifying a single pipeline stage.
    PipelineShaderStageCreateInfo es -> ShaderStageFlagBits
stage :: ShaderStageFlagBits
  , -- | @module@ is a 'Vulkan.Core10.Handles.ShaderModule' object containing the
    -- shader for this stage.
    PipelineShaderStageCreateInfo es -> ShaderModule
module' :: ShaderModule
  , -- | @pName@ is a pointer to a null-terminated UTF-8 string specifying the
    -- entry point name of the shader for this stage.
    PipelineShaderStageCreateInfo es -> ByteString
name :: ByteString
  , -- | @pSpecializationInfo@ is a pointer to a 'SpecializationInfo' structure,
    -- as described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipelines-specialization-constants Specialization Constants>,
    -- or @NULL@.
    PipelineShaderStageCreateInfo es -> Maybe SpecializationInfo
specializationInfo :: Maybe SpecializationInfo
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineShaderStageCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PipelineShaderStageCreateInfo es)

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

instance (Extendss PipelineShaderStageCreateInfo es, PokeChain es) => ToCStruct (PipelineShaderStageCreateInfo es) where
  withCStruct :: PipelineShaderStageCreateInfo es
-> (Ptr (PipelineShaderStageCreateInfo es) -> IO b) -> IO b
withCStruct x :: PipelineShaderStageCreateInfo es
x f :: Ptr (PipelineShaderStageCreateInfo es) -> IO b
f = Int
-> Int -> (Ptr (PipelineShaderStageCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr (PipelineShaderStageCreateInfo es) -> IO b) -> IO b)
-> (Ptr (PipelineShaderStageCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PipelineShaderStageCreateInfo es)
p -> Ptr (PipelineShaderStageCreateInfo es)
-> PipelineShaderStageCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PipelineShaderStageCreateInfo es)
p PipelineShaderStageCreateInfo es
x (Ptr (PipelineShaderStageCreateInfo es) -> IO b
f Ptr (PipelineShaderStageCreateInfo es)
p)
  pokeCStruct :: Ptr (PipelineShaderStageCreateInfo es)
-> PipelineShaderStageCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (PipelineShaderStageCreateInfo es)
p PipelineShaderStageCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineShaderStageCreateFlags
-> PipelineShaderStageCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es)
-> Int -> Ptr PipelineShaderStageCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineShaderStageCreateFlags)) (PipelineShaderStageCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ShaderStageFlagBits -> ShaderStageFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es)
-> Int -> Ptr ShaderStageFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ShaderStageFlagBits)) (ShaderStageFlagBits
stage)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ShaderModule -> ShaderModule -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr ShaderModule
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ShaderModule)) (ShaderModule
module')
    CString
pName'' <- ((CString -> IO b) -> IO b) -> ContT b IO CString
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((CString -> IO b) -> IO b) -> ContT b IO CString)
-> ((CString -> IO b) -> IO b) -> ContT b IO CString
forall a b. (a -> b) -> a -> b
$ ByteString -> (CString -> IO b) -> IO b
forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString (ByteString
name)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CChar))) CString
pName''
    Ptr SpecializationInfo
pSpecializationInfo'' <- case (Maybe SpecializationInfo
specializationInfo) of
      Nothing -> Ptr SpecializationInfo -> ContT b IO (Ptr SpecializationInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr SpecializationInfo
forall a. Ptr a
nullPtr
      Just j :: SpecializationInfo
j -> ((Ptr SpecializationInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SpecializationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SpecializationInfo -> IO b) -> IO b)
 -> ContT b IO (Ptr SpecializationInfo))
-> ((Ptr SpecializationInfo -> IO b) -> IO b)
-> ContT b IO (Ptr SpecializationInfo)
forall a b. (a -> b) -> a -> b
$ SpecializationInfo -> (Ptr SpecializationInfo -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SpecializationInfo
j)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr SpecializationInfo) -> Ptr SpecializationInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es)
-> Int -> Ptr (Ptr SpecializationInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SpecializationInfo))) Ptr SpecializationInfo
pSpecializationInfo''
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PipelineShaderStageCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PipelineShaderStageCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ShaderStageFlagBits -> ShaderStageFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es)
-> Int -> Ptr ShaderStageFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ShaderStageFlagBits)) (ShaderStageFlagBits
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ShaderModule -> ShaderModule -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr ShaderModule
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ShaderModule)) (ShaderModule
forall a. Zero a => a
zero)
    CString
pName'' <- ((CString -> IO b) -> IO b) -> ContT b IO CString
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((CString -> IO b) -> IO b) -> ContT b IO CString)
-> ((CString -> IO b) -> IO b) -> ContT b IO CString
forall a b. (a -> b) -> a -> b
$ ByteString -> (CString -> IO b) -> IO b
forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString (ByteString
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CChar))) CString
pName''
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PipelineShaderStageCreateInfo es, PeekChain es) => FromCStruct (PipelineShaderStageCreateInfo es) where
  peekCStruct :: Ptr (PipelineShaderStageCreateInfo es)
-> IO (PipelineShaderStageCreateInfo es)
peekCStruct p :: Ptr (PipelineShaderStageCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PipelineShaderStageCreateFlags
flags <- Ptr PipelineShaderStageCreateFlags
-> IO PipelineShaderStageCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineShaderStageCreateFlags ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es)
-> Int -> Ptr PipelineShaderStageCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineShaderStageCreateFlags))
    ShaderStageFlagBits
stage <- Ptr ShaderStageFlagBits -> IO ShaderStageFlagBits
forall a. Storable a => Ptr a -> IO a
peek @ShaderStageFlagBits ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es)
-> Int -> Ptr ShaderStageFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ShaderStageFlagBits))
    ShaderModule
module' <- Ptr ShaderModule -> IO ShaderModule
forall a. Storable a => Ptr a -> IO a
peek @ShaderModule ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr ShaderModule
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ShaderModule))
    ByteString
pName <- CString -> IO ByteString
packCString (CString -> IO ByteString) -> IO CString -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es) -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CChar)))
    Ptr SpecializationInfo
pSpecializationInfo <- Ptr (Ptr SpecializationInfo) -> IO (Ptr SpecializationInfo)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SpecializationInfo) ((Ptr (PipelineShaderStageCreateInfo es)
p Ptr (PipelineShaderStageCreateInfo es)
-> Int -> Ptr (Ptr SpecializationInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr SpecializationInfo)))
    Maybe SpecializationInfo
pSpecializationInfo' <- (Ptr SpecializationInfo -> IO SpecializationInfo)
-> Ptr SpecializationInfo -> IO (Maybe SpecializationInfo)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr SpecializationInfo
j -> Ptr SpecializationInfo -> IO SpecializationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SpecializationInfo (Ptr SpecializationInfo
j)) Ptr SpecializationInfo
pSpecializationInfo
    PipelineShaderStageCreateInfo es
-> IO (PipelineShaderStageCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineShaderStageCreateInfo es
 -> IO (PipelineShaderStageCreateInfo es))
-> PipelineShaderStageCreateInfo es
-> IO (PipelineShaderStageCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineShaderStageCreateFlags
-> ShaderStageFlagBits
-> ShaderModule
-> ByteString
-> Maybe SpecializationInfo
-> PipelineShaderStageCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineShaderStageCreateFlags
-> ShaderStageFlagBits
-> ShaderModule
-> ByteString
-> Maybe SpecializationInfo
-> PipelineShaderStageCreateInfo es
PipelineShaderStageCreateInfo
             Chain es
next PipelineShaderStageCreateFlags
flags ShaderStageFlagBits
stage ShaderModule
module' ByteString
pName Maybe SpecializationInfo
pSpecializationInfo'

instance es ~ '[] => Zero (PipelineShaderStageCreateInfo es) where
  zero :: PipelineShaderStageCreateInfo es
zero = Chain es
-> PipelineShaderStageCreateFlags
-> ShaderStageFlagBits
-> ShaderModule
-> ByteString
-> Maybe SpecializationInfo
-> PipelineShaderStageCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineShaderStageCreateFlags
-> ShaderStageFlagBits
-> ShaderModule
-> ByteString
-> Maybe SpecializationInfo
-> PipelineShaderStageCreateInfo es
PipelineShaderStageCreateInfo
           ()
           PipelineShaderStageCreateFlags
forall a. Zero a => a
zero
           ShaderStageFlagBits
forall a. Zero a => a
zero
           ShaderModule
forall a. Zero a => a
zero
           ByteString
forall a. Monoid a => a
mempty
           Maybe SpecializationInfo
forall a. Maybe a
Nothing


-- | VkComputePipelineCreateInfo - Structure specifying parameters of a newly
-- created compute pipeline
--
-- = Description
--
-- The parameters @basePipelineHandle@ and @basePipelineIndex@ are
-- described in more detail in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipelines-pipeline-derivatives Pipeline Derivatives>.
--
-- == Valid Usage
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineIndex@ is -1, @basePipelineHandle@ /must/ be
--     a valid handle to a compute 'Vulkan.Core10.Handles.Pipeline'
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineHandle@ is
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @basePipelineIndex@ /must/
--     be a valid index into the calling command’s @pCreateInfos@ parameter
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineIndex@ is not -1, @basePipelineHandle@ /must/
--     be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineHandle@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @basePipelineIndex@ /must/
--     be -1
--
-- -   The @stage@ member of @stage@ /must/ be
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_COMPUTE_BIT'
--
-- -   The shader code for the entry point identified by @stage@ and the
--     rest of the state identified by this structure /must/ adhere to the
--     pipeline linking rules described in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces Shader Interfaces>
--     chapter
--
-- -   @layout@ /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-pipelinelayout-consistency consistent>
--     with the layout of the compute shader specified in @stage@
--
-- -   The number of resources in @layout@ accessible to the compute shader
--     stage /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageResources@
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_LIBRARY_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineCreationCacheControl pipelineCreationCacheControl>
--     feature is not enabled, @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT'
--     or
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COMPUTE_PIPELINE_CREATE_INFO'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Extensions.VK_AMD_pipeline_compiler_control.PipelineCompilerControlCreateInfoAMD'
--     or
--     'Vulkan.Extensions.VK_EXT_pipeline_creation_feedback.PipelineCreationFeedbackCreateInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlagBits'
--     values
--
-- -   @stage@ /must/ be a valid 'PipelineShaderStageCreateInfo' structure
--
-- -   @layout@ /must/ be a valid 'Vulkan.Core10.Handles.PipelineLayout'
--     handle
--
-- -   Both of @basePipelineHandle@, and @layout@ that are valid handles of
--     non-ignored parameters /must/ have been created, allocated, or
--     retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Pipeline',
-- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlags',
-- 'Vulkan.Core10.Handles.PipelineLayout', 'PipelineShaderStageCreateInfo',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'createComputePipelines'
data ComputePipelineCreateInfo (es :: [Type]) = ComputePipelineCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    ComputePipelineCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlagBits'
    -- specifying how the pipeline will be generated.
    ComputePipelineCreateInfo es -> PipelineCreateFlags
flags :: PipelineCreateFlags
  , -- | @stage@ is a 'PipelineShaderStageCreateInfo' structure describing the
    -- compute shader.
    ComputePipelineCreateInfo es
-> SomeStruct PipelineShaderStageCreateInfo
stage :: SomeStruct PipelineShaderStageCreateInfo
  , -- | @layout@ is the description of binding locations used by both the
    -- pipeline and descriptor sets used with the pipeline.
    ComputePipelineCreateInfo es -> PipelineLayout
layout :: PipelineLayout
  , -- | @basePipelineHandle@ is a pipeline to derive from
    ComputePipelineCreateInfo es -> Pipeline
basePipelineHandle :: Pipeline
  , -- | @basePipelineIndex@ is an index into the @pCreateInfos@ parameter to use
    -- as a pipeline to derive from
    ComputePipelineCreateInfo es -> Int32
basePipelineIndex :: Int32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ComputePipelineCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (ComputePipelineCreateInfo es)

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

instance (Extendss ComputePipelineCreateInfo es, PokeChain es) => ToCStruct (ComputePipelineCreateInfo es) where
  withCStruct :: ComputePipelineCreateInfo es
-> (Ptr (ComputePipelineCreateInfo es) -> IO b) -> IO b
withCStruct x :: ComputePipelineCreateInfo es
x f :: Ptr (ComputePipelineCreateInfo es) -> IO b
f = Int -> Int -> (Ptr (ComputePipelineCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 96 8 ((Ptr (ComputePipelineCreateInfo es) -> IO b) -> IO b)
-> (Ptr (ComputePipelineCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (ComputePipelineCreateInfo es)
p -> Ptr (ComputePipelineCreateInfo es)
-> ComputePipelineCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (ComputePipelineCreateInfo es)
p ComputePipelineCreateInfo es
x (Ptr (ComputePipelineCreateInfo es) -> IO b
f Ptr (ComputePipelineCreateInfo es)
p)
  pokeCStruct :: Ptr (ComputePipelineCreateInfo es)
-> ComputePipelineCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (ComputePipelineCreateInfo es)
p ComputePipelineCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMPUTE_PIPELINE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineCreateFlags -> PipelineCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es)
-> Int -> Ptr PipelineCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineCreateFlags)) (PipelineCreateFlags
flags)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (SomeStruct PipelineShaderStageCreateInfo)
-> SomeStruct PipelineShaderStageCreateInfo -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (PipelineShaderStageCreateInfo Any)
-> Ptr (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es)
-> Int -> Ptr (PipelineShaderStageCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (PipelineShaderStageCreateInfo _)))) (SomeStruct PipelineShaderStageCreateInfo
stage) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineLayout -> PipelineLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr PipelineLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr PipelineLayout)) (PipelineLayout
layout)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pPipelines" ::: Ptr Pipeline) -> Pipeline -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es)
-> Int -> "pPipelines" ::: Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Pipeline)) (Pipeline
basePipelineHandle)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Int32)) (Int32
basePipelineIndex)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 96
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (ComputePipelineCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (ComputePipelineCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COMPUTE_PIPELINE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (SomeStruct PipelineShaderStageCreateInfo)
-> SomeStruct PipelineShaderStageCreateInfo -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (PipelineShaderStageCreateInfo Any)
-> Ptr (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es)
-> Int -> Ptr (PipelineShaderStageCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (PipelineShaderStageCreateInfo _)))) ((PipelineShaderStageCreateInfo '[]
-> SomeStruct PipelineShaderStageCreateInfo
forall (a :: [*] -> *) (es :: [*]).
(Extendss a es, PokeChain es, Show (Chain es)) =>
a es -> SomeStruct a
SomeStruct PipelineShaderStageCreateInfo '[]
forall a. Zero a => a
zero)) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineLayout -> PipelineLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr PipelineLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr PipelineLayout)) (PipelineLayout
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss ComputePipelineCreateInfo es, PeekChain es) => FromCStruct (ComputePipelineCreateInfo es) where
  peekCStruct :: Ptr (ComputePipelineCreateInfo es)
-> IO (ComputePipelineCreateInfo es)
peekCStruct p :: Ptr (ComputePipelineCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PipelineCreateFlags
flags <- Ptr PipelineCreateFlags -> IO PipelineCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineCreateFlags ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es)
-> Int -> Ptr PipelineCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineCreateFlags))
    SomeStruct PipelineShaderStageCreateInfo
stage <- Ptr (SomeStruct PipelineShaderStageCreateInfo)
-> IO (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (PipelineShaderStageCreateInfo Any)
-> Ptr (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es)
-> Int -> Ptr (PipelineShaderStageCreateInfo a)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (PipelineShaderStageCreateInfo a))))
    PipelineLayout
layout <- Ptr PipelineLayout -> IO PipelineLayout
forall a. Storable a => Ptr a -> IO a
peek @PipelineLayout ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr PipelineLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr PipelineLayout))
    Pipeline
basePipelineHandle <- ("pPipelines" ::: Ptr Pipeline) -> IO Pipeline
forall a. Storable a => Ptr a -> IO a
peek @Pipeline ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es)
-> Int -> "pPipelines" ::: Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr Pipeline))
    Int32
basePipelineIndex <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr (ComputePipelineCreateInfo es)
p Ptr (ComputePipelineCreateInfo es) -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Int32))
    ComputePipelineCreateInfo es -> IO (ComputePipelineCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ComputePipelineCreateInfo es -> IO (ComputePipelineCreateInfo es))
-> ComputePipelineCreateInfo es
-> IO (ComputePipelineCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineCreateFlags
-> SomeStruct PipelineShaderStageCreateInfo
-> PipelineLayout
-> Pipeline
-> Int32
-> ComputePipelineCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineCreateFlags
-> SomeStruct PipelineShaderStageCreateInfo
-> PipelineLayout
-> Pipeline
-> Int32
-> ComputePipelineCreateInfo es
ComputePipelineCreateInfo
             Chain es
next PipelineCreateFlags
flags SomeStruct PipelineShaderStageCreateInfo
stage PipelineLayout
layout Pipeline
basePipelineHandle Int32
basePipelineIndex

instance es ~ '[] => Zero (ComputePipelineCreateInfo es) where
  zero :: ComputePipelineCreateInfo es
zero = Chain es
-> PipelineCreateFlags
-> SomeStruct PipelineShaderStageCreateInfo
-> PipelineLayout
-> Pipeline
-> Int32
-> ComputePipelineCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineCreateFlags
-> SomeStruct PipelineShaderStageCreateInfo
-> PipelineLayout
-> Pipeline
-> Int32
-> ComputePipelineCreateInfo es
ComputePipelineCreateInfo
           ()
           PipelineCreateFlags
forall a. Zero a => a
zero
           (PipelineShaderStageCreateInfo '[]
-> SomeStruct PipelineShaderStageCreateInfo
forall (a :: [*] -> *) (es :: [*]).
(Extendss a es, PokeChain es, Show (Chain es)) =>
a es -> SomeStruct a
SomeStruct PipelineShaderStageCreateInfo '[]
forall a. Zero a => a
zero)
           PipelineLayout
forall a. Zero a => a
zero
           Pipeline
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero


-- | VkVertexInputBindingDescription - Structure specifying vertex input
-- binding description
--
-- == Valid Usage
--
-- -   @binding@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@
--
-- -   @stride@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindingStride@
--
-- -   If the @VK_KHR_portability_subset@ extension is enabled, @stride@
--     /must/ be a multiple of, and at least as large as,
--     'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetPropertiesKHR'::@minVertexInputBindingStrideAlignment@.
--
-- == Valid Usage (Implicit)
--
-- -   @inputRate@ /must/ be a valid
--     'Vulkan.Core10.Enums.VertexInputRate.VertexInputRate' value
--
-- = See Also
--
-- 'PipelineVertexInputStateCreateInfo',
-- 'Vulkan.Core10.Enums.VertexInputRate.VertexInputRate'
data VertexInputBindingDescription = VertexInputBindingDescription
  { -- | @binding@ is the binding number that this structure describes.
    VertexInputBindingDescription -> "createInfoCount" ::: Word32
binding :: Word32
  , -- | @stride@ is the distance in bytes between two consecutive elements
    -- within the buffer.
    VertexInputBindingDescription -> "createInfoCount" ::: Word32
stride :: Word32
  , -- | @inputRate@ is a 'Vulkan.Core10.Enums.VertexInputRate.VertexInputRate'
    -- value specifying whether vertex attribute addressing is a function of
    -- the vertex index or of the instance index.
    VertexInputBindingDescription -> VertexInputRate
inputRate :: VertexInputRate
  }
  deriving (Typeable, VertexInputBindingDescription
-> VertexInputBindingDescription -> Bool
(VertexInputBindingDescription
 -> VertexInputBindingDescription -> Bool)
-> (VertexInputBindingDescription
    -> VertexInputBindingDescription -> Bool)
-> Eq VertexInputBindingDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VertexInputBindingDescription
-> VertexInputBindingDescription -> Bool
$c/= :: VertexInputBindingDescription
-> VertexInputBindingDescription -> Bool
== :: VertexInputBindingDescription
-> VertexInputBindingDescription -> Bool
$c== :: VertexInputBindingDescription
-> VertexInputBindingDescription -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (VertexInputBindingDescription)
#endif
deriving instance Show VertexInputBindingDescription

instance ToCStruct VertexInputBindingDescription where
  withCStruct :: VertexInputBindingDescription
-> (Ptr VertexInputBindingDescription -> IO b) -> IO b
withCStruct x :: VertexInputBindingDescription
x f :: Ptr VertexInputBindingDescription -> IO b
f = Int -> Int -> (Ptr VertexInputBindingDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 12 4 ((Ptr VertexInputBindingDescription -> IO b) -> IO b)
-> (Ptr VertexInputBindingDescription -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr VertexInputBindingDescription
p -> Ptr VertexInputBindingDescription
-> VertexInputBindingDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr VertexInputBindingDescription
p VertexInputBindingDescription
x (Ptr VertexInputBindingDescription -> IO b
f Ptr VertexInputBindingDescription
p)
  pokeCStruct :: Ptr VertexInputBindingDescription
-> VertexInputBindingDescription -> IO b -> IO b
pokeCStruct p :: Ptr VertexInputBindingDescription
p VertexInputBindingDescription{..} f :: IO b
f = do
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputBindingDescription
p Ptr VertexInputBindingDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("createInfoCount" ::: Word32
binding)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputBindingDescription
p Ptr VertexInputBindingDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("createInfoCount" ::: Word32
stride)
    Ptr VertexInputRate -> VertexInputRate -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputBindingDescription
p Ptr VertexInputBindingDescription -> Int -> Ptr VertexInputRate
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr VertexInputRate)) (VertexInputRate
inputRate)
    IO b
f
  cStructSize :: Int
cStructSize = 12
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr VertexInputBindingDescription -> IO b -> IO b
pokeZeroCStruct p :: Ptr VertexInputBindingDescription
p f :: IO b
f = do
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputBindingDescription
p Ptr VertexInputBindingDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputBindingDescription
p Ptr VertexInputBindingDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr VertexInputRate -> VertexInputRate -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputBindingDescription
p Ptr VertexInputBindingDescription -> Int -> Ptr VertexInputRate
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr VertexInputRate)) (VertexInputRate
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct VertexInputBindingDescription where
  peekCStruct :: Ptr VertexInputBindingDescription
-> IO VertexInputBindingDescription
peekCStruct p :: Ptr VertexInputBindingDescription
p = do
    "createInfoCount" ::: Word32
binding <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr VertexInputBindingDescription
p Ptr VertexInputBindingDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    "createInfoCount" ::: Word32
stride <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr VertexInputBindingDescription
p Ptr VertexInputBindingDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    VertexInputRate
inputRate <- Ptr VertexInputRate -> IO VertexInputRate
forall a. Storable a => Ptr a -> IO a
peek @VertexInputRate ((Ptr VertexInputBindingDescription
p Ptr VertexInputBindingDescription -> Int -> Ptr VertexInputRate
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr VertexInputRate))
    VertexInputBindingDescription -> IO VertexInputBindingDescription
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VertexInputBindingDescription -> IO VertexInputBindingDescription)
-> VertexInputBindingDescription
-> IO VertexInputBindingDescription
forall a b. (a -> b) -> a -> b
$ ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> VertexInputRate
-> VertexInputBindingDescription
VertexInputBindingDescription
             "createInfoCount" ::: Word32
binding "createInfoCount" ::: Word32
stride VertexInputRate
inputRate

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

instance Zero VertexInputBindingDescription where
  zero :: VertexInputBindingDescription
zero = ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> VertexInputRate
-> VertexInputBindingDescription
VertexInputBindingDescription
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           VertexInputRate
forall a. Zero a => a
zero


-- | VkVertexInputAttributeDescription - Structure specifying vertex input
-- attribute description
--
-- == Valid Usage
--
-- -   @location@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputAttributes@
--
-- -   @binding@ /must/ be less than
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@
--
-- -   @offset@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputAttributeOffset@
--
-- -   @format@ /must/ be allowed as a vertex buffer format, as specified
--     by the
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_VERTEX_BUFFER_BIT'
--     flag in
--     'Vulkan.Core10.DeviceInitialization.FormatProperties'::@bufferFeatures@
--     returned by
--     'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceFormatProperties'
--
-- -   If the @VK_KHR_portability_subset@ extension is enabled, and
--     'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetFeaturesKHR'::@vertexAttributeAccessBeyondStride@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', the sum of @offset@ plus
--     the size of the vertex attribute data described by @format@ /must/
--     not be greater than @stride@ in the 'VertexInputBindingDescription'
--     referenced in @binding@.
--
-- == Valid Usage (Implicit)
--
-- -   @format@ /must/ be a valid 'Vulkan.Core10.Enums.Format.Format' value
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'PipelineVertexInputStateCreateInfo'
data VertexInputAttributeDescription = VertexInputAttributeDescription
  { -- | @location@ is the shader binding location number for this attribute.
    VertexInputAttributeDescription -> "createInfoCount" ::: Word32
location :: Word32
  , -- | @binding@ is the binding number which this attribute takes its data
    -- from.
    VertexInputAttributeDescription -> "createInfoCount" ::: Word32
binding :: Word32
  , -- | @format@ is the size and type of the vertex attribute data.
    VertexInputAttributeDescription -> Format
format :: Format
  , -- | @offset@ is a byte offset of this attribute relative to the start of an
    -- element in the vertex input binding.
    VertexInputAttributeDescription -> "createInfoCount" ::: Word32
offset :: Word32
  }
  deriving (Typeable, VertexInputAttributeDescription
-> VertexInputAttributeDescription -> Bool
(VertexInputAttributeDescription
 -> VertexInputAttributeDescription -> Bool)
-> (VertexInputAttributeDescription
    -> VertexInputAttributeDescription -> Bool)
-> Eq VertexInputAttributeDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VertexInputAttributeDescription
-> VertexInputAttributeDescription -> Bool
$c/= :: VertexInputAttributeDescription
-> VertexInputAttributeDescription -> Bool
== :: VertexInputAttributeDescription
-> VertexInputAttributeDescription -> Bool
$c== :: VertexInputAttributeDescription
-> VertexInputAttributeDescription -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (VertexInputAttributeDescription)
#endif
deriving instance Show VertexInputAttributeDescription

instance ToCStruct VertexInputAttributeDescription where
  withCStruct :: VertexInputAttributeDescription
-> (Ptr VertexInputAttributeDescription -> IO b) -> IO b
withCStruct x :: VertexInputAttributeDescription
x f :: Ptr VertexInputAttributeDescription -> IO b
f = Int -> Int -> (Ptr VertexInputAttributeDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((Ptr VertexInputAttributeDescription -> IO b) -> IO b)
-> (Ptr VertexInputAttributeDescription -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr VertexInputAttributeDescription
p -> Ptr VertexInputAttributeDescription
-> VertexInputAttributeDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr VertexInputAttributeDescription
p VertexInputAttributeDescription
x (Ptr VertexInputAttributeDescription -> IO b
f Ptr VertexInputAttributeDescription
p)
  pokeCStruct :: Ptr VertexInputAttributeDescription
-> VertexInputAttributeDescription -> IO b -> IO b
pokeCStruct p :: Ptr VertexInputAttributeDescription
p VertexInputAttributeDescription{..} f :: IO b
f = do
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("createInfoCount" ::: Word32
location)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("createInfoCount" ::: Word32
binding)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Format)) (Format
format)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) ("createInfoCount" ::: Word32
offset)
    IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr VertexInputAttributeDescription -> IO b -> IO b
pokeZeroCStruct p :: Ptr VertexInputAttributeDescription
p f :: IO b
f = do
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct VertexInputAttributeDescription where
  peekCStruct :: Ptr VertexInputAttributeDescription
-> IO VertexInputAttributeDescription
peekCStruct p :: Ptr VertexInputAttributeDescription
p = do
    "createInfoCount" ::: Word32
location <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    "createInfoCount" ::: Word32
binding <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Format))
    "createInfoCount" ::: Word32
offset <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr VertexInputAttributeDescription
p Ptr VertexInputAttributeDescription
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    VertexInputAttributeDescription
-> IO VertexInputAttributeDescription
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VertexInputAttributeDescription
 -> IO VertexInputAttributeDescription)
-> VertexInputAttributeDescription
-> IO VertexInputAttributeDescription
forall a b. (a -> b) -> a -> b
$ ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> Format
-> ("createInfoCount" ::: Word32)
-> VertexInputAttributeDescription
VertexInputAttributeDescription
             "createInfoCount" ::: Word32
location "createInfoCount" ::: Word32
binding Format
format "createInfoCount" ::: Word32
offset

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

instance Zero VertexInputAttributeDescription where
  zero :: VertexInputAttributeDescription
zero = ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> Format
-> ("createInfoCount" ::: Word32)
-> VertexInputAttributeDescription
VertexInputAttributeDescription
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           Format
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero


-- | VkPipelineVertexInputStateCreateInfo - Structure specifying parameters
-- of a newly created pipeline vertex input state
--
-- == Valid Usage
--
-- -   @vertexBindingDescriptionCount@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputBindings@
--
-- -   @vertexAttributeDescriptionCount@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxVertexInputAttributes@
--
-- -   For every @binding@ specified by each element of
--     @pVertexAttributeDescriptions@, a 'VertexInputBindingDescription'
--     /must/ exist in @pVertexBindingDescriptions@ with the same value of
--     @binding@
--
-- -   All elements of @pVertexBindingDescriptions@ /must/ describe
--     distinct binding numbers
--
-- -   All elements of @pVertexAttributeDescriptions@ /must/ describe
--     distinct attribute locations
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_STATE_CREATE_INFO'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_vertex_attribute_divisor.PipelineVertexInputDivisorStateCreateInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be @0@
--
-- -   If @vertexBindingDescriptionCount@ is not @0@,
--     @pVertexBindingDescriptions@ /must/ be a valid pointer to an array
--     of @vertexBindingDescriptionCount@ valid
--     'VertexInputBindingDescription' structures
--
-- -   If @vertexAttributeDescriptionCount@ is not @0@,
--     @pVertexAttributeDescriptions@ /must/ be a valid pointer to an array
--     of @vertexAttributeDescriptionCount@ valid
--     'VertexInputAttributeDescription' structures
--
-- = See Also
--
-- 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.GraphicsShaderGroupCreateInfoNV',
-- 'Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags.PipelineVertexInputStateCreateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'VertexInputAttributeDescription', 'VertexInputBindingDescription'
data PipelineVertexInputStateCreateInfo (es :: [Type]) = PipelineVertexInputStateCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PipelineVertexInputStateCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    PipelineVertexInputStateCreateInfo es
-> PipelineVertexInputStateCreateFlags
flags :: PipelineVertexInputStateCreateFlags
  , -- | @pVertexBindingDescriptions@ is a pointer to an array of
    -- 'VertexInputBindingDescription' structures.
    PipelineVertexInputStateCreateInfo es
-> Vector VertexInputBindingDescription
vertexBindingDescriptions :: Vector VertexInputBindingDescription
  , -- | @pVertexAttributeDescriptions@ is a pointer to an array of
    -- 'VertexInputAttributeDescription' structures.
    PipelineVertexInputStateCreateInfo es
-> Vector VertexInputAttributeDescription
vertexAttributeDescriptions :: Vector VertexInputAttributeDescription
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineVertexInputStateCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PipelineVertexInputStateCreateInfo es)

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

instance (Extendss PipelineVertexInputStateCreateInfo es, PokeChain es) => ToCStruct (PipelineVertexInputStateCreateInfo es) where
  withCStruct :: PipelineVertexInputStateCreateInfo es
-> (Ptr (PipelineVertexInputStateCreateInfo es) -> IO b) -> IO b
withCStruct x :: PipelineVertexInputStateCreateInfo es
x f :: Ptr (PipelineVertexInputStateCreateInfo es) -> IO b
f = Int
-> Int
-> (Ptr (PipelineVertexInputStateCreateInfo es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr (PipelineVertexInputStateCreateInfo es) -> IO b) -> IO b)
-> (Ptr (PipelineVertexInputStateCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PipelineVertexInputStateCreateInfo es)
p -> Ptr (PipelineVertexInputStateCreateInfo es)
-> PipelineVertexInputStateCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PipelineVertexInputStateCreateInfo es)
p PipelineVertexInputStateCreateInfo es
x (Ptr (PipelineVertexInputStateCreateInfo es) -> IO b
f Ptr (PipelineVertexInputStateCreateInfo es)
p)
  pokeCStruct :: Ptr (PipelineVertexInputStateCreateInfo es)
-> PipelineVertexInputStateCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (PipelineVertexInputStateCreateInfo es)
p PipelineVertexInputStateCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_STATE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineVertexInputStateCreateFlags
-> PipelineVertexInputStateCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr PipelineVertexInputStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineVertexInputStateCreateFlags)) (PipelineVertexInputStateCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector VertexInputBindingDescription -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector VertexInputBindingDescription -> Int)
-> Vector VertexInputBindingDescription -> Int
forall a b. (a -> b) -> a -> b
$ (Vector VertexInputBindingDescription
vertexBindingDescriptions)) :: Word32))
    Ptr VertexInputBindingDescription
pPVertexBindingDescriptions' <- ((Ptr VertexInputBindingDescription -> IO b) -> IO b)
-> ContT b IO (Ptr VertexInputBindingDescription)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr VertexInputBindingDescription -> IO b) -> IO b)
 -> ContT b IO (Ptr VertexInputBindingDescription))
-> ((Ptr VertexInputBindingDescription -> IO b) -> IO b)
-> ContT b IO (Ptr VertexInputBindingDescription)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr VertexInputBindingDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @VertexInputBindingDescription ((Vector VertexInputBindingDescription -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector VertexInputBindingDescription
vertexBindingDescriptions)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 12) 4
    (Int -> VertexInputBindingDescription -> ContT b IO ())
-> Vector VertexInputBindingDescription -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: VertexInputBindingDescription
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr VertexInputBindingDescription
-> VertexInputBindingDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr VertexInputBindingDescription
pPVertexBindingDescriptions' Ptr VertexInputBindingDescription
-> Int -> Ptr VertexInputBindingDescription
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr VertexInputBindingDescription) (VertexInputBindingDescription
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector VertexInputBindingDescription
vertexBindingDescriptions)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr VertexInputBindingDescription)
-> Ptr VertexInputBindingDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr (Ptr VertexInputBindingDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr VertexInputBindingDescription))) (Ptr VertexInputBindingDescription
pPVertexBindingDescriptions')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector VertexInputAttributeDescription -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector VertexInputAttributeDescription -> Int)
-> Vector VertexInputAttributeDescription -> Int
forall a b. (a -> b) -> a -> b
$ (Vector VertexInputAttributeDescription
vertexAttributeDescriptions)) :: Word32))
    Ptr VertexInputAttributeDescription
pPVertexAttributeDescriptions' <- ((Ptr VertexInputAttributeDescription -> IO b) -> IO b)
-> ContT b IO (Ptr VertexInputAttributeDescription)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr VertexInputAttributeDescription -> IO b) -> IO b)
 -> ContT b IO (Ptr VertexInputAttributeDescription))
-> ((Ptr VertexInputAttributeDescription -> IO b) -> IO b)
-> ContT b IO (Ptr VertexInputAttributeDescription)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr VertexInputAttributeDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @VertexInputAttributeDescription ((Vector VertexInputAttributeDescription -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector VertexInputAttributeDescription
vertexAttributeDescriptions)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
    (Int -> VertexInputAttributeDescription -> ContT b IO ())
-> Vector VertexInputAttributeDescription -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: VertexInputAttributeDescription
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr VertexInputAttributeDescription
-> VertexInputAttributeDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr VertexInputAttributeDescription
pPVertexAttributeDescriptions' Ptr VertexInputAttributeDescription
-> Int -> Ptr VertexInputAttributeDescription
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr VertexInputAttributeDescription) (VertexInputAttributeDescription
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector VertexInputAttributeDescription
vertexAttributeDescriptions)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr VertexInputAttributeDescription)
-> Ptr VertexInputAttributeDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr (Ptr VertexInputAttributeDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr VertexInputAttributeDescription))) (Ptr VertexInputAttributeDescription
pPVertexAttributeDescriptions')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PipelineVertexInputStateCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PipelineVertexInputStateCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_STATE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    Ptr VertexInputBindingDescription
pPVertexBindingDescriptions' <- ((Ptr VertexInputBindingDescription -> IO b) -> IO b)
-> ContT b IO (Ptr VertexInputBindingDescription)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr VertexInputBindingDescription -> IO b) -> IO b)
 -> ContT b IO (Ptr VertexInputBindingDescription))
-> ((Ptr VertexInputBindingDescription -> IO b) -> IO b)
-> ContT b IO (Ptr VertexInputBindingDescription)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr VertexInputBindingDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @VertexInputBindingDescription ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 12) 4
    (Int -> VertexInputBindingDescription -> ContT b IO ())
-> Vector VertexInputBindingDescription -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: VertexInputBindingDescription
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr VertexInputBindingDescription
-> VertexInputBindingDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr VertexInputBindingDescription
pPVertexBindingDescriptions' Ptr VertexInputBindingDescription
-> Int -> Ptr VertexInputBindingDescription
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr VertexInputBindingDescription) (VertexInputBindingDescription
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector VertexInputBindingDescription
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr VertexInputBindingDescription)
-> Ptr VertexInputBindingDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr (Ptr VertexInputBindingDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr VertexInputBindingDescription))) (Ptr VertexInputBindingDescription
pPVertexBindingDescriptions')
    Ptr VertexInputAttributeDescription
pPVertexAttributeDescriptions' <- ((Ptr VertexInputAttributeDescription -> IO b) -> IO b)
-> ContT b IO (Ptr VertexInputAttributeDescription)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr VertexInputAttributeDescription -> IO b) -> IO b)
 -> ContT b IO (Ptr VertexInputAttributeDescription))
-> ((Ptr VertexInputAttributeDescription -> IO b) -> IO b)
-> ContT b IO (Ptr VertexInputAttributeDescription)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr VertexInputAttributeDescription -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @VertexInputAttributeDescription ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
    (Int -> VertexInputAttributeDescription -> ContT b IO ())
-> Vector VertexInputAttributeDescription -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: VertexInputAttributeDescription
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr VertexInputAttributeDescription
-> VertexInputAttributeDescription -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr VertexInputAttributeDescription
pPVertexAttributeDescriptions' Ptr VertexInputAttributeDescription
-> Int -> Ptr VertexInputAttributeDescription
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr VertexInputAttributeDescription) (VertexInputAttributeDescription
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector VertexInputAttributeDescription
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr VertexInputAttributeDescription)
-> Ptr VertexInputAttributeDescription -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr (Ptr VertexInputAttributeDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr VertexInputAttributeDescription))) (Ptr VertexInputAttributeDescription
pPVertexAttributeDescriptions')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PipelineVertexInputStateCreateInfo es, PeekChain es) => FromCStruct (PipelineVertexInputStateCreateInfo es) where
  peekCStruct :: Ptr (PipelineVertexInputStateCreateInfo es)
-> IO (PipelineVertexInputStateCreateInfo es)
peekCStruct p :: Ptr (PipelineVertexInputStateCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PipelineVertexInputStateCreateFlags
flags <- Ptr PipelineVertexInputStateCreateFlags
-> IO PipelineVertexInputStateCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineVertexInputStateCreateFlags ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr PipelineVertexInputStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineVertexInputStateCreateFlags))
    "createInfoCount" ::: Word32
vertexBindingDescriptionCount <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr VertexInputBindingDescription
pVertexBindingDescriptions <- Ptr (Ptr VertexInputBindingDescription)
-> IO (Ptr VertexInputBindingDescription)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr VertexInputBindingDescription) ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr (Ptr VertexInputBindingDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr VertexInputBindingDescription)))
    Vector VertexInputBindingDescription
pVertexBindingDescriptions' <- Int
-> (Int -> IO VertexInputBindingDescription)
-> IO (Vector VertexInputBindingDescription)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "createInfoCount" ::: Word32
vertexBindingDescriptionCount) (\i :: Int
i -> Ptr VertexInputBindingDescription
-> IO VertexInputBindingDescription
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @VertexInputBindingDescription ((Ptr VertexInputBindingDescription
pVertexBindingDescriptions Ptr VertexInputBindingDescription
-> Int -> Ptr VertexInputBindingDescription
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr VertexInputBindingDescription)))
    "createInfoCount" ::: Word32
vertexAttributeDescriptionCount <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr VertexInputAttributeDescription
pVertexAttributeDescriptions <- Ptr (Ptr VertexInputAttributeDescription)
-> IO (Ptr VertexInputAttributeDescription)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr VertexInputAttributeDescription) ((Ptr (PipelineVertexInputStateCreateInfo es)
p Ptr (PipelineVertexInputStateCreateInfo es)
-> Int -> Ptr (Ptr VertexInputAttributeDescription)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr VertexInputAttributeDescription)))
    Vector VertexInputAttributeDescription
pVertexAttributeDescriptions' <- Int
-> (Int -> IO VertexInputAttributeDescription)
-> IO (Vector VertexInputAttributeDescription)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "createInfoCount" ::: Word32
vertexAttributeDescriptionCount) (\i :: Int
i -> Ptr VertexInputAttributeDescription
-> IO VertexInputAttributeDescription
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @VertexInputAttributeDescription ((Ptr VertexInputAttributeDescription
pVertexAttributeDescriptions Ptr VertexInputAttributeDescription
-> Int -> Ptr VertexInputAttributeDescription
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr VertexInputAttributeDescription)))
    PipelineVertexInputStateCreateInfo es
-> IO (PipelineVertexInputStateCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineVertexInputStateCreateInfo es
 -> IO (PipelineVertexInputStateCreateInfo es))
-> PipelineVertexInputStateCreateInfo es
-> IO (PipelineVertexInputStateCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineVertexInputStateCreateFlags
-> Vector VertexInputBindingDescription
-> Vector VertexInputAttributeDescription
-> PipelineVertexInputStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineVertexInputStateCreateFlags
-> Vector VertexInputBindingDescription
-> Vector VertexInputAttributeDescription
-> PipelineVertexInputStateCreateInfo es
PipelineVertexInputStateCreateInfo
             Chain es
next PipelineVertexInputStateCreateFlags
flags Vector VertexInputBindingDescription
pVertexBindingDescriptions' Vector VertexInputAttributeDescription
pVertexAttributeDescriptions'

instance es ~ '[] => Zero (PipelineVertexInputStateCreateInfo es) where
  zero :: PipelineVertexInputStateCreateInfo es
zero = Chain es
-> PipelineVertexInputStateCreateFlags
-> Vector VertexInputBindingDescription
-> Vector VertexInputAttributeDescription
-> PipelineVertexInputStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineVertexInputStateCreateFlags
-> Vector VertexInputBindingDescription
-> Vector VertexInputAttributeDescription
-> PipelineVertexInputStateCreateInfo es
PipelineVertexInputStateCreateInfo
           ()
           PipelineVertexInputStateCreateFlags
forall a. Zero a => a
zero
           Vector VertexInputBindingDescription
forall a. Monoid a => a
mempty
           Vector VertexInputAttributeDescription
forall a. Monoid a => a
mempty


-- | VkPipelineInputAssemblyStateCreateInfo - Structure specifying parameters
-- of a newly created pipeline input assembly state
--
-- = Description
--
-- Restarting the assembly of primitives discards the most recent index
-- values if those elements formed an incomplete primitive, and restarts
-- the primitive assembly using the subsequent indices, but only assembling
-- the immediately following element through the end of the originally
-- specified elements. The primitive restart index value comparison is
-- performed before adding the @vertexOffset@ value to the index value.
--
-- == Valid Usage
--
-- -   If @topology@ is
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_POINT_LIST',
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_LINE_LIST',
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_TRIANGLE_LIST',
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_LINE_LIST_WITH_ADJACENCY',
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_TRIANGLE_LIST_WITH_ADJACENCY'
--     or
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_PATCH_LIST',
--     @primitiveRestartEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @topology@ /must/ not be any of
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_LINE_LIST_WITH_ADJACENCY',
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_LINE_STRIP_WITH_ADJACENCY',
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_TRIANGLE_LIST_WITH_ADJACENCY'
--     or
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_TRIANGLE_STRIP_WITH_ADJACENCY'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @topology@ /must/ not be
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_PATCH_LIST'
--
-- -   If the @VK_KHR_portability_subset@ extension is enabled, and
--     'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetFeaturesKHR'::@triangleFans@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', @topology@ /must/ not be
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_TRIANGLE_FAN'.
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_INPUT_ASSEMBLY_STATE_CREATE_INFO'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @flags@ /must/ be @0@
--
-- -   @topology@ /must/ be a valid
--     'Vulkan.Core10.Enums.PrimitiveTopology.PrimitiveTopology' value
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags.PipelineInputAssemblyStateCreateFlags',
-- 'Vulkan.Core10.Enums.PrimitiveTopology.PrimitiveTopology',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineInputAssemblyStateCreateInfo = PipelineInputAssemblyStateCreateInfo
  { -- | @flags@ is reserved for future use.
    PipelineInputAssemblyStateCreateInfo
-> PipelineInputAssemblyStateCreateFlags
flags :: PipelineInputAssemblyStateCreateFlags
  , -- | @topology@ is a
    -- 'Vulkan.Core10.Enums.PrimitiveTopology.PrimitiveTopology' defining the
    -- primitive topology, as described below.
    PipelineInputAssemblyStateCreateInfo -> PrimitiveTopology
topology :: PrimitiveTopology
  , -- | @primitiveRestartEnable@ controls whether a special vertex index value
    -- is treated as restarting the assembly of primitives. This enable only
    -- applies to indexed draws
    -- ('Vulkan.Core10.CommandBufferBuilding.cmdDrawIndexed' and
    -- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndexedIndirect'), and the
    -- special index value is either 0xFFFFFFFF when the @indexType@ parameter
    -- of 'Vulkan.Core10.CommandBufferBuilding.cmdBindIndexBuffer' is equal to
    -- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT32', 0xFF when @indexType@
    -- is equal to 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT8_EXT', or
    -- 0xFFFF when @indexType@ is equal to
    -- 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT16'. Primitive restart is
    -- not allowed for “list” topologies.
    PipelineInputAssemblyStateCreateInfo -> Bool
primitiveRestartEnable :: Bool
  }
  deriving (Typeable, PipelineInputAssemblyStateCreateInfo
-> PipelineInputAssemblyStateCreateInfo -> Bool
(PipelineInputAssemblyStateCreateInfo
 -> PipelineInputAssemblyStateCreateInfo -> Bool)
-> (PipelineInputAssemblyStateCreateInfo
    -> PipelineInputAssemblyStateCreateInfo -> Bool)
-> Eq PipelineInputAssemblyStateCreateInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineInputAssemblyStateCreateInfo
-> PipelineInputAssemblyStateCreateInfo -> Bool
$c/= :: PipelineInputAssemblyStateCreateInfo
-> PipelineInputAssemblyStateCreateInfo -> Bool
== :: PipelineInputAssemblyStateCreateInfo
-> PipelineInputAssemblyStateCreateInfo -> Bool
$c== :: PipelineInputAssemblyStateCreateInfo
-> PipelineInputAssemblyStateCreateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineInputAssemblyStateCreateInfo)
#endif
deriving instance Show PipelineInputAssemblyStateCreateInfo

instance ToCStruct PipelineInputAssemblyStateCreateInfo where
  withCStruct :: PipelineInputAssemblyStateCreateInfo
-> (Ptr PipelineInputAssemblyStateCreateInfo -> IO b) -> IO b
withCStruct x :: PipelineInputAssemblyStateCreateInfo
x f :: Ptr PipelineInputAssemblyStateCreateInfo -> IO b
f = Int
-> Int
-> (Ptr PipelineInputAssemblyStateCreateInfo -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PipelineInputAssemblyStateCreateInfo -> IO b) -> IO b)
-> (Ptr PipelineInputAssemblyStateCreateInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PipelineInputAssemblyStateCreateInfo
p -> Ptr PipelineInputAssemblyStateCreateInfo
-> PipelineInputAssemblyStateCreateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineInputAssemblyStateCreateInfo
p PipelineInputAssemblyStateCreateInfo
x (Ptr PipelineInputAssemblyStateCreateInfo -> IO b
f Ptr PipelineInputAssemblyStateCreateInfo
p)
  pokeCStruct :: Ptr PipelineInputAssemblyStateCreateInfo
-> PipelineInputAssemblyStateCreateInfo -> IO b -> IO b
pokeCStruct p :: Ptr PipelineInputAssemblyStateCreateInfo
p PipelineInputAssemblyStateCreateInfo{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_INPUT_ASSEMBLY_STATE_CREATE_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr PipelineInputAssemblyStateCreateFlags
-> PipelineInputAssemblyStateCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo
-> Int -> Ptr PipelineInputAssemblyStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineInputAssemblyStateCreateFlags)) (PipelineInputAssemblyStateCreateFlags
flags)
    Ptr PrimitiveTopology -> PrimitiveTopology -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo
-> Int -> Ptr PrimitiveTopology
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr PrimitiveTopology)) (PrimitiveTopology
topology)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
primitiveRestartEnable))
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PipelineInputAssemblyStateCreateInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineInputAssemblyStateCreateInfo
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_INPUT_ASSEMBLY_STATE_CREATE_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr PrimitiveTopology -> PrimitiveTopology -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo
-> Int -> Ptr PrimitiveTopology
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr PrimitiveTopology)) (PrimitiveTopology
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PipelineInputAssemblyStateCreateInfo where
  peekCStruct :: Ptr PipelineInputAssemblyStateCreateInfo
-> IO PipelineInputAssemblyStateCreateInfo
peekCStruct p :: Ptr PipelineInputAssemblyStateCreateInfo
p = do
    PipelineInputAssemblyStateCreateFlags
flags <- Ptr PipelineInputAssemblyStateCreateFlags
-> IO PipelineInputAssemblyStateCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineInputAssemblyStateCreateFlags ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo
-> Int -> Ptr PipelineInputAssemblyStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineInputAssemblyStateCreateFlags))
    PrimitiveTopology
topology <- Ptr PrimitiveTopology -> IO PrimitiveTopology
forall a. Storable a => Ptr a -> IO a
peek @PrimitiveTopology ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo
-> Int -> Ptr PrimitiveTopology
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr PrimitiveTopology))
    Bool32
primitiveRestartEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineInputAssemblyStateCreateInfo
p Ptr PipelineInputAssemblyStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    PipelineInputAssemblyStateCreateInfo
-> IO PipelineInputAssemblyStateCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineInputAssemblyStateCreateInfo
 -> IO PipelineInputAssemblyStateCreateInfo)
-> PipelineInputAssemblyStateCreateInfo
-> IO PipelineInputAssemblyStateCreateInfo
forall a b. (a -> b) -> a -> b
$ PipelineInputAssemblyStateCreateFlags
-> PrimitiveTopology
-> Bool
-> PipelineInputAssemblyStateCreateInfo
PipelineInputAssemblyStateCreateInfo
             PipelineInputAssemblyStateCreateFlags
flags PrimitiveTopology
topology (Bool32 -> Bool
bool32ToBool Bool32
primitiveRestartEnable)

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

instance Zero PipelineInputAssemblyStateCreateInfo where
  zero :: PipelineInputAssemblyStateCreateInfo
zero = PipelineInputAssemblyStateCreateFlags
-> PrimitiveTopology
-> Bool
-> PipelineInputAssemblyStateCreateInfo
PipelineInputAssemblyStateCreateInfo
           PipelineInputAssemblyStateCreateFlags
forall a. Zero a => a
zero
           PrimitiveTopology
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkPipelineTessellationStateCreateInfo - Structure specifying parameters
-- of a newly created pipeline tessellation state
--
-- == Valid Usage
--
-- -   @patchControlPoints@ /must/ be greater than zero and less than or
--     equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxTessellationPatchSize@
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_TESSELLATION_STATE_CREATE_INFO'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.PipelineTessellationDomainOriginStateCreateInfo'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be @0@
--
-- = See Also
--
-- 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.GraphicsShaderGroupCreateInfoNV',
-- 'Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags.PipelineTessellationStateCreateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineTessellationStateCreateInfo (es :: [Type]) = PipelineTessellationStateCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PipelineTessellationStateCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    PipelineTessellationStateCreateInfo es
-> PipelineTessellationStateCreateFlags
flags :: PipelineTessellationStateCreateFlags
  , -- | @patchControlPoints@ number of control points per patch.
    PipelineTessellationStateCreateInfo es
-> "createInfoCount" ::: Word32
patchControlPoints :: Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineTessellationStateCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PipelineTessellationStateCreateInfo es)

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

instance (Extendss PipelineTessellationStateCreateInfo es, PokeChain es) => ToCStruct (PipelineTessellationStateCreateInfo es) where
  withCStruct :: PipelineTessellationStateCreateInfo es
-> (Ptr (PipelineTessellationStateCreateInfo es) -> IO b) -> IO b
withCStruct x :: PipelineTessellationStateCreateInfo es
x f :: Ptr (PipelineTessellationStateCreateInfo es) -> IO b
f = Int
-> Int
-> (Ptr (PipelineTessellationStateCreateInfo es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr (PipelineTessellationStateCreateInfo es) -> IO b) -> IO b)
-> (Ptr (PipelineTessellationStateCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PipelineTessellationStateCreateInfo es)
p -> Ptr (PipelineTessellationStateCreateInfo es)
-> PipelineTessellationStateCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PipelineTessellationStateCreateInfo es)
p PipelineTessellationStateCreateInfo es
x (Ptr (PipelineTessellationStateCreateInfo es) -> IO b
f Ptr (PipelineTessellationStateCreateInfo es)
p)
  pokeCStruct :: Ptr (PipelineTessellationStateCreateInfo es)
-> PipelineTessellationStateCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (PipelineTessellationStateCreateInfo es)
p PipelineTessellationStateCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_TESSELLATION_STATE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineTessellationStateCreateFlags
-> PipelineTessellationStateCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es)
-> Int -> Ptr PipelineTessellationStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineTessellationStateCreateFlags)) (PipelineTessellationStateCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("createInfoCount" ::: Word32
patchControlPoints)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PipelineTessellationStateCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PipelineTessellationStateCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_TESSELLATION_STATE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PipelineTessellationStateCreateInfo es, PeekChain es) => FromCStruct (PipelineTessellationStateCreateInfo es) where
  peekCStruct :: Ptr (PipelineTessellationStateCreateInfo es)
-> IO (PipelineTessellationStateCreateInfo es)
peekCStruct p :: Ptr (PipelineTessellationStateCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PipelineTessellationStateCreateFlags
flags <- Ptr PipelineTessellationStateCreateFlags
-> IO PipelineTessellationStateCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineTessellationStateCreateFlags ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es)
-> Int -> Ptr PipelineTessellationStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineTessellationStateCreateFlags))
    "createInfoCount" ::: Word32
patchControlPoints <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (PipelineTessellationStateCreateInfo es)
p Ptr (PipelineTessellationStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    PipelineTessellationStateCreateInfo es
-> IO (PipelineTessellationStateCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineTessellationStateCreateInfo es
 -> IO (PipelineTessellationStateCreateInfo es))
-> PipelineTessellationStateCreateInfo es
-> IO (PipelineTessellationStateCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineTessellationStateCreateFlags
-> ("createInfoCount" ::: Word32)
-> PipelineTessellationStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineTessellationStateCreateFlags
-> ("createInfoCount" ::: Word32)
-> PipelineTessellationStateCreateInfo es
PipelineTessellationStateCreateInfo
             Chain es
next PipelineTessellationStateCreateFlags
flags "createInfoCount" ::: Word32
patchControlPoints

instance es ~ '[] => Zero (PipelineTessellationStateCreateInfo es) where
  zero :: PipelineTessellationStateCreateInfo es
zero = Chain es
-> PipelineTessellationStateCreateFlags
-> ("createInfoCount" ::: Word32)
-> PipelineTessellationStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineTessellationStateCreateFlags
-> ("createInfoCount" ::: Word32)
-> PipelineTessellationStateCreateInfo es
PipelineTessellationStateCreateInfo
           ()
           PipelineTessellationStateCreateFlags
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero


-- | VkPipelineViewportStateCreateInfo - Structure specifying parameters of a
-- newly created pipeline viewport state
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports>
--     feature is not enabled, @viewportCount@ /must/ not be greater than
--     @1@
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-multiViewport multiple viewports>
--     feature is not enabled, @scissorCount@ /must/ not be greater than
--     @1@
--
-- -   @viewportCount@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@
--
-- -   @scissorCount@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxViewports@
--
-- -   The @x@ and @y@ members of @offset@ member of any element of
--     @pScissors@ /must/ be greater than or equal to @0@
--
-- -   Evaluation of (@offset.x@ + @extent.width@) /must/ not cause a
--     signed integer addition overflow for any element of @pScissors@
--
-- -   Evaluation of (@offset.y@ + @extent.height@) /must/ not cause a
--     signed integer addition overflow for any element of @pScissors@
--
-- -   If the graphics pipeline is being created without
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     set then @scissorCount@ and @viewportCount@ /must/ be identical
--
-- -   If the graphics pipeline is being created with
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     set then @viewportCount@ /must/ be @0@, otherwise it /must/ be
--     greater than @0@
--
-- -   If the graphics pipeline is being created with
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     set then @scissorCount@ /must/ be @0@, otherwise it /must/ be
--     greater than @0@
--
-- -   If the @viewportWScalingEnable@ member of a
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'
--     structure included in the @pNext@ chain is
--     'Vulkan.Core10.FundamentalTypes.TRUE', the @viewportCount@ member of
--     the
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'
--     structure /must/ be greater than or equal to
--     'PipelineViewportStateCreateInfo'::@viewportCount@
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_VIEWPORT_STATE_CREATE_INFO'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportCoarseSampleOrderStateCreateInfoNV',
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV',
--     'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV',
--     'Vulkan.Extensions.VK_NV_viewport_swizzle.PipelineViewportSwizzleStateCreateInfoNV',
--     or
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be @0@
--
-- = See Also
--
-- 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Core10.Enums.PipelineViewportStateCreateFlags.PipelineViewportStateCreateFlags',
-- 'Vulkan.Core10.FundamentalTypes.Rect2D',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'Viewport'
data PipelineViewportStateCreateInfo (es :: [Type]) = PipelineViewportStateCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PipelineViewportStateCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    PipelineViewportStateCreateInfo es
-> PipelineViewportStateCreateFlags
flags :: PipelineViewportStateCreateFlags
  , -- | @viewportCount@ is the number of viewports used by the pipeline.
    PipelineViewportStateCreateInfo es -> "createInfoCount" ::: Word32
viewportCount :: Word32
  , -- | @pViewports@ is a pointer to an array of 'Viewport' structures, defining
    -- the viewport transforms. If the viewport state is dynamic, this member
    -- is ignored.
    PipelineViewportStateCreateInfo es -> Vector Viewport
viewports :: Vector Viewport
  , -- | @scissorCount@ is the number of
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-scissor scissors>
    -- and /must/ match the number of viewports.
    PipelineViewportStateCreateInfo es -> "createInfoCount" ::: Word32
scissorCount :: Word32
  , -- | @pScissors@ is a pointer to an array of
    -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures defining the
    -- rectangular bounds of the scissor for the corresponding viewport. If the
    -- scissor state is dynamic, this member is ignored.
    PipelineViewportStateCreateInfo es -> Vector Rect2D
scissors :: Vector Rect2D
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineViewportStateCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PipelineViewportStateCreateInfo es)

instance Extensible PipelineViewportStateCreateInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_PIPELINE_VIEWPORT_STATE_CREATE_INFO
  setNext :: PipelineViewportStateCreateInfo ds
-> Chain es -> PipelineViewportStateCreateInfo es
setNext x :: PipelineViewportStateCreateInfo ds
x next :: Chain es
next = PipelineViewportStateCreateInfo ds
x{$sel:next:PipelineViewportStateCreateInfo :: Chain es
next = Chain es
next}
  getNext :: PipelineViewportStateCreateInfo es -> Chain es
getNext PipelineViewportStateCreateInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends PipelineViewportStateCreateInfo e => b) -> Maybe b
  extends :: proxy e
-> (Extends PipelineViewportStateCreateInfo e => b) -> Maybe b
extends _ f :: Extends PipelineViewportStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineViewportCoarseSampleOrderStateCreateInfoNV) =>
Maybe (e :~: PipelineViewportCoarseSampleOrderStateCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineViewportCoarseSampleOrderStateCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineViewportStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineViewportShadingRateImageStateCreateInfoNV) =>
Maybe (e :~: PipelineViewportShadingRateImageStateCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineViewportShadingRateImageStateCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineViewportStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineViewportExclusiveScissorStateCreateInfoNV) =>
Maybe (e :~: PipelineViewportExclusiveScissorStateCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineViewportExclusiveScissorStateCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineViewportStateCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable PipelineViewportSwizzleStateCreateInfoNV) =>
Maybe (e :~: PipelineViewportSwizzleStateCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineViewportSwizzleStateCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineViewportStateCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable PipelineViewportWScalingStateCreateInfoNV) =>
Maybe (e :~: PipelineViewportWScalingStateCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineViewportWScalingStateCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineViewportStateCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss PipelineViewportStateCreateInfo es, PokeChain es) => ToCStruct (PipelineViewportStateCreateInfo es) where
  withCStruct :: PipelineViewportStateCreateInfo es
-> (Ptr (PipelineViewportStateCreateInfo es) -> IO b) -> IO b
withCStruct x :: PipelineViewportStateCreateInfo es
x f :: Ptr (PipelineViewportStateCreateInfo es) -> IO b
f = Int
-> Int
-> (Ptr (PipelineViewportStateCreateInfo es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr (PipelineViewportStateCreateInfo es) -> IO b) -> IO b)
-> (Ptr (PipelineViewportStateCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PipelineViewportStateCreateInfo es)
p -> Ptr (PipelineViewportStateCreateInfo es)
-> PipelineViewportStateCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PipelineViewportStateCreateInfo es)
p PipelineViewportStateCreateInfo es
x (Ptr (PipelineViewportStateCreateInfo es) -> IO b
f Ptr (PipelineViewportStateCreateInfo es)
p)
  pokeCStruct :: Ptr (PipelineViewportStateCreateInfo es)
-> PipelineViewportStateCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (PipelineViewportStateCreateInfo es)
p PipelineViewportStateCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_VIEWPORT_STATE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineViewportStateCreateFlags
-> PipelineViewportStateCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr PipelineViewportStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineViewportStateCreateFlags)) (PipelineViewportStateCreateFlags
flags)
    let pViewportsLength :: Int
pViewportsLength = Vector Viewport -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Viewport -> Int) -> Vector Viewport -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Viewport
viewports)
    "createInfoCount" ::: Word32
viewportCount'' <- IO ("createInfoCount" ::: Word32)
-> ContT b IO ("createInfoCount" ::: Word32)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("createInfoCount" ::: Word32)
 -> ContT b IO ("createInfoCount" ::: Word32))
-> IO ("createInfoCount" ::: Word32)
-> ContT b IO ("createInfoCount" ::: Word32)
forall a b. (a -> b) -> a -> b
$ if ("createInfoCount" ::: Word32
viewportCount) ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> Bool
forall a. Eq a => a -> a -> Bool
== 0
      then ("createInfoCount" ::: Word32) -> IO ("createInfoCount" ::: Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("createInfoCount" ::: Word32)
 -> IO ("createInfoCount" ::: Word32))
-> ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a b. (a -> b) -> a -> b
$ Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pViewportsLength
      else do
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pViewportsLength ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> Bool
forall a. Eq a => a -> a -> Bool
== ("createInfoCount" ::: Word32
viewportCount) Bool -> Bool -> Bool
|| Int
pViewportsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
          IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "pViewports must be empty or have 'viewportCount' elements" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
        ("createInfoCount" ::: Word32) -> IO ("createInfoCount" ::: Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ("createInfoCount" ::: Word32
viewportCount)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("createInfoCount" ::: Word32
viewportCount'')
    Ptr Viewport
pViewports'' <- if Vector Viewport -> Bool
forall a. Vector a -> Bool
Data.Vector.null (Vector Viewport
viewports)
      then Ptr Viewport -> ContT b IO (Ptr Viewport)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr Viewport
forall a. Ptr a
nullPtr
      else do
        Ptr Viewport
pPViewports <- ((Ptr Viewport -> IO b) -> IO b) -> ContT b IO (Ptr Viewport)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Viewport -> IO b) -> IO b) -> ContT b IO (Ptr Viewport))
-> ((Ptr Viewport -> IO b) -> IO b) -> ContT b IO (Ptr Viewport)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Viewport -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Viewport (((Vector Viewport -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Viewport
viewports))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 4
        (Int -> Viewport -> ContT b IO ())
-> Vector Viewport -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Viewport
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Viewport -> Viewport -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Viewport
pPViewports Ptr Viewport -> Int -> Ptr Viewport
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Viewport) (Viewport
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) ((Vector Viewport
viewports))
        Ptr Viewport -> ContT b IO (Ptr Viewport)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr Viewport -> ContT b IO (Ptr Viewport))
-> Ptr Viewport -> ContT b IO (Ptr Viewport)
forall a b. (a -> b) -> a -> b
$ Ptr Viewport
pPViewports
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Viewport) -> Ptr Viewport -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr (Ptr Viewport)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Viewport))) Ptr Viewport
pViewports''
    let pScissorsLength :: Int
pScissorsLength = Vector Rect2D -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Rect2D -> Int) -> Vector Rect2D -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Rect2D
scissors)
    "createInfoCount" ::: Word32
scissorCount'' <- IO ("createInfoCount" ::: Word32)
-> ContT b IO ("createInfoCount" ::: Word32)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("createInfoCount" ::: Word32)
 -> ContT b IO ("createInfoCount" ::: Word32))
-> IO ("createInfoCount" ::: Word32)
-> ContT b IO ("createInfoCount" ::: Word32)
forall a b. (a -> b) -> a -> b
$ if ("createInfoCount" ::: Word32
scissorCount) ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> Bool
forall a. Eq a => a -> a -> Bool
== 0
      then ("createInfoCount" ::: Word32) -> IO ("createInfoCount" ::: Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("createInfoCount" ::: Word32)
 -> IO ("createInfoCount" ::: Word32))
-> ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a b. (a -> b) -> a -> b
$ Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pScissorsLength
      else do
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pScissorsLength ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> Bool
forall a. Eq a => a -> a -> Bool
== ("createInfoCount" ::: Word32
scissorCount) Bool -> Bool -> Bool
|| Int
pScissorsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
          IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "pScissors must be empty or have 'scissorCount' elements" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
        ("createInfoCount" ::: Word32) -> IO ("createInfoCount" ::: Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ("createInfoCount" ::: Word32
scissorCount)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ("createInfoCount" ::: Word32
scissorCount'')
    Ptr Rect2D
pScissors'' <- if Vector Rect2D -> Bool
forall a. Vector a -> Bool
Data.Vector.null (Vector Rect2D
scissors)
      then Ptr Rect2D -> ContT b IO (Ptr Rect2D)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr Rect2D
forall a. Ptr a
nullPtr
      else do
        Ptr Rect2D
pPScissors <- ((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D))
-> ((Ptr Rect2D -> IO b) -> IO b) -> ContT b IO (Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Rect2D -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Rect2D (((Vector Rect2D -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Rect2D
scissors))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 16) 4
        (Int -> Rect2D -> ContT b IO ()) -> Vector Rect2D -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Rect2D
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Rect2D -> Rect2D -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr Rect2D
pPScissors Ptr Rect2D -> Int -> Ptr Rect2D
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D) (Rect2D
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) ((Vector Rect2D
scissors))
        Ptr Rect2D -> ContT b IO (Ptr Rect2D)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr Rect2D -> ContT b IO (Ptr Rect2D))
-> Ptr Rect2D -> ContT b IO (Ptr Rect2D)
forall a b. (a -> b) -> a -> b
$ Ptr Rect2D
pPScissors
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Rect2D) -> Ptr Rect2D -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es) -> Int -> Ptr (Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr Rect2D))) Ptr Rect2D
pScissors''
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PipelineViewportStateCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PipelineViewportStateCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_VIEWPORT_STATE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PipelineViewportStateCreateInfo es, PeekChain es) => FromCStruct (PipelineViewportStateCreateInfo es) where
  peekCStruct :: Ptr (PipelineViewportStateCreateInfo es)
-> IO (PipelineViewportStateCreateInfo es)
peekCStruct p :: Ptr (PipelineViewportStateCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PipelineViewportStateCreateFlags
flags <- Ptr PipelineViewportStateCreateFlags
-> IO PipelineViewportStateCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineViewportStateCreateFlags ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr PipelineViewportStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineViewportStateCreateFlags))
    "createInfoCount" ::: Word32
viewportCount <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr Viewport
pViewports <- Ptr (Ptr Viewport) -> IO (Ptr Viewport)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Viewport) ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr (Ptr Viewport)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Viewport)))
    let pViewportsLength :: Int
pViewportsLength = if Ptr Viewport
pViewports Ptr Viewport -> Ptr Viewport -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Viewport
forall a. Ptr a
nullPtr then 0 else (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "createInfoCount" ::: Word32
viewportCount)
    Vector Viewport
pViewports' <- Int -> (Int -> IO Viewport) -> IO (Vector Viewport)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM Int
pViewportsLength (\i :: Int
i -> Ptr Viewport -> IO Viewport
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Viewport ((Ptr Viewport
pViewports Ptr Viewport -> Int -> Ptr Viewport
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Viewport)))
    "createInfoCount" ::: Word32
scissorCount <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr Rect2D
pScissors <- Ptr (Ptr Rect2D) -> IO (Ptr Rect2D)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Rect2D) ((Ptr (PipelineViewportStateCreateInfo es)
p Ptr (PipelineViewportStateCreateInfo es) -> Int -> Ptr (Ptr Rect2D)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr Rect2D)))
    let pScissorsLength :: Int
pScissorsLength = if Ptr Rect2D
pScissors Ptr Rect2D -> Ptr Rect2D -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Rect2D
forall a. Ptr a
nullPtr then 0 else (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "createInfoCount" ::: Word32
scissorCount)
    Vector Rect2D
pScissors' <- Int -> (Int -> IO Rect2D) -> IO (Vector Rect2D)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM Int
pScissorsLength (\i :: Int
i -> Ptr Rect2D -> IO Rect2D
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Rect2D ((Ptr Rect2D
pScissors Ptr Rect2D -> Int -> Ptr Rect2D
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (16 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Rect2D)))
    PipelineViewportStateCreateInfo es
-> IO (PipelineViewportStateCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineViewportStateCreateInfo es
 -> IO (PipelineViewportStateCreateInfo es))
-> PipelineViewportStateCreateInfo es
-> IO (PipelineViewportStateCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineViewportStateCreateFlags
-> ("createInfoCount" ::: Word32)
-> Vector Viewport
-> ("createInfoCount" ::: Word32)
-> Vector Rect2D
-> PipelineViewportStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineViewportStateCreateFlags
-> ("createInfoCount" ::: Word32)
-> Vector Viewport
-> ("createInfoCount" ::: Word32)
-> Vector Rect2D
-> PipelineViewportStateCreateInfo es
PipelineViewportStateCreateInfo
             Chain es
next PipelineViewportStateCreateFlags
flags "createInfoCount" ::: Word32
viewportCount Vector Viewport
pViewports' "createInfoCount" ::: Word32
scissorCount Vector Rect2D
pScissors'

instance es ~ '[] => Zero (PipelineViewportStateCreateInfo es) where
  zero :: PipelineViewportStateCreateInfo es
zero = Chain es
-> PipelineViewportStateCreateFlags
-> ("createInfoCount" ::: Word32)
-> Vector Viewport
-> ("createInfoCount" ::: Word32)
-> Vector Rect2D
-> PipelineViewportStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineViewportStateCreateFlags
-> ("createInfoCount" ::: Word32)
-> Vector Viewport
-> ("createInfoCount" ::: Word32)
-> Vector Rect2D
-> PipelineViewportStateCreateInfo es
PipelineViewportStateCreateInfo
           ()
           PipelineViewportStateCreateFlags
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           Vector Viewport
forall a. Monoid a => a
mempty
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           Vector Rect2D
forall a. Monoid a => a
mempty


-- | VkPipelineRasterizationStateCreateInfo - Structure specifying parameters
-- of a newly created pipeline rasterization state
--
-- = Description
--
-- The application /can/ also add a
-- 'Vulkan.Extensions.VK_AMD_rasterization_order.PipelineRasterizationStateRasterizationOrderAMD'
-- structure to the @pNext@ chain of a
-- 'PipelineRasterizationStateCreateInfo' structure. This structure enables
-- selecting the rasterization order to use when rendering with the
-- corresponding graphics pipeline as described in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primrast-order Rasterization Order>.
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthClamp depth clamping>
--     feature is not enabled, @depthClampEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-fillModeNonSolid non-solid fill modes>
--     feature is not enabled, @polygonMode@ /must/ be
--     'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_FILL' or
--     'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_FILL_RECTANGLE_NV'
--
-- -   If the @VK_NV_fill_rectangle@ extension is not enabled,
--     @polygonMode@ /must/ not be
--     'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_FILL_RECTANGLE_NV'
--
-- -   If the @VK_KHR_portability_subset@ extension is enabled, and
--     'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetFeaturesKHR'::@pointPolygons@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', and
--     @rasterizerDiscardEnable@ is 'Vulkan.Core10.FundamentalTypes.FALSE',
--     @polygonMode@ /must/ not be
--     'Vulkan.Core10.Enums.PolygonMode.POLYGON_MODE_POINT'.
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_CREATE_INFO'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Extensions.VK_EXT_conservative_rasterization.PipelineRasterizationConservativeStateCreateInfoEXT',
--     'Vulkan.Extensions.VK_EXT_depth_clip_enable.PipelineRasterizationDepthClipStateCreateInfoEXT',
--     'Vulkan.Extensions.VK_EXT_line_rasterization.PipelineRasterizationLineStateCreateInfoEXT',
--     'Vulkan.Extensions.VK_AMD_rasterization_order.PipelineRasterizationStateRasterizationOrderAMD',
--     or
--     'Vulkan.Extensions.VK_EXT_transform_feedback.PipelineRasterizationStateStreamCreateInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be @0@
--
-- -   @polygonMode@ /must/ be a valid
--     'Vulkan.Core10.Enums.PolygonMode.PolygonMode' value
--
-- -   @cullMode@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.CullModeFlagBits.CullModeFlagBits' values
--
-- -   @frontFace@ /must/ be a valid
--     'Vulkan.Core10.Enums.FrontFace.FrontFace' value
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.CullModeFlagBits.CullModeFlags',
-- 'Vulkan.Core10.Enums.FrontFace.FrontFace', 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags.PipelineRasterizationStateCreateFlags',
-- 'Vulkan.Core10.Enums.PolygonMode.PolygonMode',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineRasterizationStateCreateInfo (es :: [Type]) = PipelineRasterizationStateCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PipelineRasterizationStateCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    PipelineRasterizationStateCreateInfo es
-> PipelineRasterizationStateCreateFlags
flags :: PipelineRasterizationStateCreateFlags
  , -- | @depthClampEnable@ controls whether to clamp the fragment’s depth values
    -- as described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-depth Depth Test>.
    -- If the pipeline is not created with
    -- 'Vulkan.Extensions.VK_EXT_depth_clip_enable.PipelineRasterizationDepthClipStateCreateInfoEXT'
    -- present then enabling depth clamp will also disable clipping primitives
    -- to the z planes of the frustrum as described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vertexpostproc-clipping Primitive Clipping>.
    -- Otherwise depth clipping is controlled by the state set in
    -- 'Vulkan.Extensions.VK_EXT_depth_clip_enable.PipelineRasterizationDepthClipStateCreateInfoEXT'.
    PipelineRasterizationStateCreateInfo es -> Bool
depthClampEnable :: Bool
  , -- | @rasterizerDiscardEnable@ controls whether primitives are discarded
    -- immediately before the rasterization stage.
    PipelineRasterizationStateCreateInfo es -> Bool
rasterizerDiscardEnable :: Bool
  , -- | @polygonMode@ is the triangle rendering mode. See
    -- 'Vulkan.Core10.Enums.PolygonMode.PolygonMode'.
    PipelineRasterizationStateCreateInfo es -> PolygonMode
polygonMode :: PolygonMode
  , -- | @cullMode@ is the triangle facing direction used for primitive culling.
    -- See 'Vulkan.Core10.Enums.CullModeFlagBits.CullModeFlagBits'.
    PipelineRasterizationStateCreateInfo es -> CullModeFlags
cullMode :: CullModeFlags
  , -- | @frontFace@ is a 'Vulkan.Core10.Enums.FrontFace.FrontFace' value
    -- specifying the front-facing triangle orientation to be used for culling.
    PipelineRasterizationStateCreateInfo es -> FrontFace
frontFace :: FrontFace
  , -- | @depthBiasEnable@ controls whether to bias fragment depth values.
    PipelineRasterizationStateCreateInfo es -> Bool
depthBiasEnable :: Bool
  , -- | @depthBiasConstantFactor@ is a scalar factor controlling the constant
    -- depth value added to each fragment.
    PipelineRasterizationStateCreateInfo es -> Float
depthBiasConstantFactor :: Float
  , -- | @depthBiasClamp@ is the maximum (or minimum) depth bias of a fragment.
    PipelineRasterizationStateCreateInfo es -> Float
depthBiasClamp :: Float
  , -- | @depthBiasSlopeFactor@ is a scalar factor applied to a fragment’s slope
    -- in depth bias calculations.
    PipelineRasterizationStateCreateInfo es -> Float
depthBiasSlopeFactor :: Float
  , -- | @lineWidth@ is the width of rasterized line segments.
    PipelineRasterizationStateCreateInfo es -> Float
lineWidth :: Float
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineRasterizationStateCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PipelineRasterizationStateCreateInfo es)

instance Extensible PipelineRasterizationStateCreateInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_CREATE_INFO
  setNext :: PipelineRasterizationStateCreateInfo ds
-> Chain es -> PipelineRasterizationStateCreateInfo es
setNext x :: PipelineRasterizationStateCreateInfo ds
x next :: Chain es
next = PipelineRasterizationStateCreateInfo ds
x{$sel:next:PipelineRasterizationStateCreateInfo :: Chain es
next = Chain es
next}
  getNext :: PipelineRasterizationStateCreateInfo es -> Chain es
getNext PipelineRasterizationStateCreateInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends PipelineRasterizationStateCreateInfo e => b) -> Maybe b
  extends :: proxy e
-> (Extends PipelineRasterizationStateCreateInfo e => b) -> Maybe b
extends _ f :: Extends PipelineRasterizationStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineRasterizationLineStateCreateInfoEXT) =>
Maybe (e :~: PipelineRasterizationLineStateCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineRasterizationLineStateCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineRasterizationStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineRasterizationDepthClipStateCreateInfoEXT) =>
Maybe (e :~: PipelineRasterizationDepthClipStateCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineRasterizationDepthClipStateCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineRasterizationStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineRasterizationStateStreamCreateInfoEXT) =>
Maybe (e :~: PipelineRasterizationStateStreamCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineRasterizationStateStreamCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineRasterizationStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineRasterizationConservativeStateCreateInfoEXT) =>
Maybe (e :~: PipelineRasterizationConservativeStateCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineRasterizationConservativeStateCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineRasterizationStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineRasterizationStateRasterizationOrderAMD) =>
Maybe (e :~: PipelineRasterizationStateRasterizationOrderAMD)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineRasterizationStateRasterizationOrderAMD = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineRasterizationStateCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss PipelineRasterizationStateCreateInfo es, PokeChain es) => ToCStruct (PipelineRasterizationStateCreateInfo es) where
  withCStruct :: PipelineRasterizationStateCreateInfo es
-> (Ptr (PipelineRasterizationStateCreateInfo es) -> IO b) -> IO b
withCStruct x :: PipelineRasterizationStateCreateInfo es
x f :: Ptr (PipelineRasterizationStateCreateInfo es) -> IO b
f = Int
-> Int
-> (Ptr (PipelineRasterizationStateCreateInfo es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr (PipelineRasterizationStateCreateInfo es) -> IO b) -> IO b)
-> (Ptr (PipelineRasterizationStateCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PipelineRasterizationStateCreateInfo es)
p -> Ptr (PipelineRasterizationStateCreateInfo es)
-> PipelineRasterizationStateCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PipelineRasterizationStateCreateInfo es)
p PipelineRasterizationStateCreateInfo es
x (Ptr (PipelineRasterizationStateCreateInfo es) -> IO b
f Ptr (PipelineRasterizationStateCreateInfo es)
p)
  pokeCStruct :: Ptr (PipelineRasterizationStateCreateInfo es)
-> PipelineRasterizationStateCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (PipelineRasterizationStateCreateInfo es)
p PipelineRasterizationStateCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineRasterizationStateCreateFlags
-> PipelineRasterizationStateCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr PipelineRasterizationStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineRasterizationStateCreateFlags)) (PipelineRasterizationStateCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthClampEnable))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rasterizerDiscardEnable))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PolygonMode -> PolygonMode -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr PolygonMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr PolygonMode)) (PolygonMode
polygonMode)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CullModeFlags -> CullModeFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr CullModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr CullModeFlags)) (CullModeFlags
cullMode)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr FrontFace -> FrontFace -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr FrontFace
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr FrontFace)) (FrontFace
frontFace)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthBiasEnable))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
depthBiasConstantFactor))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
depthBiasClamp))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
depthBiasSlopeFactor))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
lineWidth))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PipelineRasterizationStateCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PipelineRasterizationStateCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PolygonMode -> PolygonMode -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr PolygonMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr PolygonMode)) (PolygonMode
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr FrontFace -> FrontFace -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr FrontFace
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr FrontFace)) (FrontFace
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PipelineRasterizationStateCreateInfo es, PeekChain es) => FromCStruct (PipelineRasterizationStateCreateInfo es) where
  peekCStruct :: Ptr (PipelineRasterizationStateCreateInfo es)
-> IO (PipelineRasterizationStateCreateInfo es)
peekCStruct p :: Ptr (PipelineRasterizationStateCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PipelineRasterizationStateCreateFlags
flags <- Ptr PipelineRasterizationStateCreateFlags
-> IO PipelineRasterizationStateCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineRasterizationStateCreateFlags ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr PipelineRasterizationStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineRasterizationStateCreateFlags))
    Bool32
depthClampEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Bool32
rasterizerDiscardEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    PolygonMode
polygonMode <- Ptr PolygonMode -> IO PolygonMode
forall a. Storable a => Ptr a -> IO a
peek @PolygonMode ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr PolygonMode
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr PolygonMode))
    CullModeFlags
cullMode <- Ptr CullModeFlags -> IO CullModeFlags
forall a. Storable a => Ptr a -> IO a
peek @CullModeFlags ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr CullModeFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr CullModeFlags))
    FrontFace
frontFace <- Ptr FrontFace -> IO FrontFace
forall a. Storable a => Ptr a -> IO a
peek @FrontFace ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es)
-> Int -> Ptr FrontFace
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr FrontFace))
    Bool32
depthBiasEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32))
    CFloat
depthBiasConstantFactor <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr CFloat))
    CFloat
depthBiasClamp <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr CFloat))
    CFloat
depthBiasSlopeFactor <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr CFloat))
    CFloat
lineWidth <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr (PipelineRasterizationStateCreateInfo es)
p Ptr (PipelineRasterizationStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr CFloat))
    PipelineRasterizationStateCreateInfo es
-> IO (PipelineRasterizationStateCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineRasterizationStateCreateInfo es
 -> IO (PipelineRasterizationStateCreateInfo es))
-> PipelineRasterizationStateCreateInfo es
-> IO (PipelineRasterizationStateCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineRasterizationStateCreateFlags
-> Bool
-> Bool
-> PolygonMode
-> CullModeFlags
-> FrontFace
-> Bool
-> Float
-> Float
-> Float
-> Float
-> PipelineRasterizationStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineRasterizationStateCreateFlags
-> Bool
-> Bool
-> PolygonMode
-> CullModeFlags
-> FrontFace
-> Bool
-> Float
-> Float
-> Float
-> Float
-> PipelineRasterizationStateCreateInfo es
PipelineRasterizationStateCreateInfo
             Chain es
next PipelineRasterizationStateCreateFlags
flags (Bool32 -> Bool
bool32ToBool Bool32
depthClampEnable) (Bool32 -> Bool
bool32ToBool Bool32
rasterizerDiscardEnable) PolygonMode
polygonMode CullModeFlags
cullMode FrontFace
frontFace (Bool32 -> Bool
bool32ToBool Bool32
depthBiasEnable) ((\(CFloat a :: Float
a) -> Float
a) CFloat
depthBiasConstantFactor) ((\(CFloat a :: Float
a) -> Float
a) CFloat
depthBiasClamp) ((\(CFloat a :: Float
a) -> Float
a) CFloat
depthBiasSlopeFactor) ((\(CFloat a :: Float
a) -> Float
a) CFloat
lineWidth)

instance es ~ '[] => Zero (PipelineRasterizationStateCreateInfo es) where
  zero :: PipelineRasterizationStateCreateInfo es
zero = Chain es
-> PipelineRasterizationStateCreateFlags
-> Bool
-> Bool
-> PolygonMode
-> CullModeFlags
-> FrontFace
-> Bool
-> Float
-> Float
-> Float
-> Float
-> PipelineRasterizationStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineRasterizationStateCreateFlags
-> Bool
-> Bool
-> PolygonMode
-> CullModeFlags
-> FrontFace
-> Bool
-> Float
-> Float
-> Float
-> Float
-> PipelineRasterizationStateCreateInfo es
PipelineRasterizationStateCreateInfo
           ()
           PipelineRasterizationStateCreateFlags
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           PolygonMode
forall a. Zero a => a
zero
           CullModeFlags
forall a. Zero a => a
zero
           FrontFace
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero


-- | VkPipelineMultisampleStateCreateInfo - Structure specifying parameters
-- of a newly created pipeline multisample state
--
-- = Description
--
-- Each bit in the sample mask is associated with a unique
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-multisampling-coverage-mask sample index>
-- as defined for the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-multisampling-coverage-mask coverage mask>.
-- Each bit b for mask word w in the sample mask corresponds to sample
-- index i, where i = 32 × w + b. @pSampleMask@ has a length equal to ⌈
-- @rasterizationSamples@ \/ 32 ⌉ words.
--
-- If @pSampleMask@ is @NULL@, it is treated as if the mask has all bits
-- set to @1@.
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sampleRateShading sample rate shading>
--     feature is not enabled, @sampleShadingEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-alphaToOne alpha to one>
--     feature is not enabled, @alphaToOneEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- -   @minSampleShading@ /must/ be in the range [0,1]
--
-- -   If the @VK_NV_framebuffer_mixed_samples@ extension is enabled, and
--     if the subpass has any color attachments and @rasterizationSamples@
--     is greater than the number of color samples, then
--     @sampleShadingEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_MULTISAMPLE_STATE_CREATE_INFO'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Extensions.VK_NV_framebuffer_mixed_samples.PipelineCoverageModulationStateCreateInfoNV',
--     'Vulkan.Extensions.VK_NV_coverage_reduction_mode.PipelineCoverageReductionStateCreateInfoNV',
--     'Vulkan.Extensions.VK_NV_fragment_coverage_to_color.PipelineCoverageToColorStateCreateInfoNV',
--     or
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be @0@
--
-- -   @rasterizationSamples@ /must/ be a valid
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' value
--
-- -   If @pSampleMask@ is not @NULL@, @pSampleMask@ /must/ be a valid
--     pointer to an array of
--     \(\lceil{\mathit{rasterizationSamples} \over 32}\rceil\)
--     'Vulkan.Core10.FundamentalTypes.SampleMask' values
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags.PipelineMultisampleStateCreateFlags',
-- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits',
-- 'Vulkan.Core10.FundamentalTypes.SampleMask',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineMultisampleStateCreateInfo (es :: [Type]) = PipelineMultisampleStateCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PipelineMultisampleStateCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    PipelineMultisampleStateCreateInfo es
-> PipelineMultisampleStateCreateFlags
flags :: PipelineMultisampleStateCreateFlags
  , -- | @rasterizationSamples@ is a
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' specifying
    -- the number of samples used in rasterization.
    PipelineMultisampleStateCreateInfo es -> SampleCountFlagBits
rasterizationSamples :: SampleCountFlagBits
  , -- | @sampleShadingEnable@ /can/ be used to enable
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#primsrast-sampleshading Sample Shading>.
    PipelineMultisampleStateCreateInfo es -> Bool
sampleShadingEnable :: Bool
  , -- | @minSampleShading@ specifies a minimum fraction of sample shading if
    -- @sampleShadingEnable@ is set to 'Vulkan.Core10.FundamentalTypes.TRUE'.
    PipelineMultisampleStateCreateInfo es -> Float
minSampleShading :: Float
  , -- | @pSampleMask@ is an array of 'Vulkan.Core10.FundamentalTypes.SampleMask'
    -- values used in the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-samplemask sample mask test>.
    PipelineMultisampleStateCreateInfo es
-> Vector ("createInfoCount" ::: Word32)
sampleMask :: Vector SampleMask
  , -- | @alphaToCoverageEnable@ controls whether a temporary coverage value is
    -- generated based on the alpha component of the fragment’s first color
    -- output as specified in the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-covg Multisample Coverage>
    -- section.
    PipelineMultisampleStateCreateInfo es -> Bool
alphaToCoverageEnable :: Bool
  , -- | @alphaToOneEnable@ controls whether the alpha component of the
    -- fragment’s first color output is replaced with one as described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-covg Multisample Coverage>.
    PipelineMultisampleStateCreateInfo es -> Bool
alphaToOneEnable :: Bool
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineMultisampleStateCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PipelineMultisampleStateCreateInfo es)

instance Extensible PipelineMultisampleStateCreateInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_PIPELINE_MULTISAMPLE_STATE_CREATE_INFO
  setNext :: PipelineMultisampleStateCreateInfo ds
-> Chain es -> PipelineMultisampleStateCreateInfo es
setNext x :: PipelineMultisampleStateCreateInfo ds
x next :: Chain es
next = PipelineMultisampleStateCreateInfo ds
x{$sel:next:PipelineMultisampleStateCreateInfo :: Chain es
next = Chain es
next}
  getNext :: PipelineMultisampleStateCreateInfo es -> Chain es
getNext PipelineMultisampleStateCreateInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends PipelineMultisampleStateCreateInfo e => b) -> Maybe b
  extends :: proxy e
-> (Extends PipelineMultisampleStateCreateInfo e => b) -> Maybe b
extends _ f :: Extends PipelineMultisampleStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineCoverageReductionStateCreateInfoNV) =>
Maybe (e :~: PipelineCoverageReductionStateCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineCoverageReductionStateCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineMultisampleStateCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineCoverageModulationStateCreateInfoNV) =>
Maybe (e :~: PipelineCoverageModulationStateCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineCoverageModulationStateCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineMultisampleStateCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable PipelineSampleLocationsStateCreateInfoEXT) =>
Maybe (e :~: PipelineSampleLocationsStateCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineSampleLocationsStateCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineMultisampleStateCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable PipelineCoverageToColorStateCreateInfoNV) =>
Maybe (e :~: PipelineCoverageToColorStateCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineCoverageToColorStateCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PipelineMultisampleStateCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss PipelineMultisampleStateCreateInfo es, PokeChain es) => ToCStruct (PipelineMultisampleStateCreateInfo es) where
  withCStruct :: PipelineMultisampleStateCreateInfo es
-> (Ptr (PipelineMultisampleStateCreateInfo es) -> IO b) -> IO b
withCStruct x :: PipelineMultisampleStateCreateInfo es
x f :: Ptr (PipelineMultisampleStateCreateInfo es) -> IO b
f = Int
-> Int
-> (Ptr (PipelineMultisampleStateCreateInfo es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr (PipelineMultisampleStateCreateInfo es) -> IO b) -> IO b)
-> (Ptr (PipelineMultisampleStateCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PipelineMultisampleStateCreateInfo es)
p -> Ptr (PipelineMultisampleStateCreateInfo es)
-> PipelineMultisampleStateCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PipelineMultisampleStateCreateInfo es)
p PipelineMultisampleStateCreateInfo es
x (Ptr (PipelineMultisampleStateCreateInfo es) -> IO b
f Ptr (PipelineMultisampleStateCreateInfo es)
p)
  pokeCStruct :: Ptr (PipelineMultisampleStateCreateInfo es)
-> PipelineMultisampleStateCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (PipelineMultisampleStateCreateInfo es)
p PipelineMultisampleStateCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_MULTISAMPLE_STATE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineMultisampleStateCreateFlags
-> PipelineMultisampleStateCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es)
-> Int -> Ptr PipelineMultisampleStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineMultisampleStateCreateFlags)) (PipelineMultisampleStateCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
rasterizationSamples)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
sampleShadingEnable))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
minSampleShading))
    Ptr ("createInfoCount" ::: Word32)
pSampleMask'' <- case Vector ("createInfoCount" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("createInfoCount" ::: Word32)
sampleMask) of
      0      -> Ptr ("createInfoCount" ::: Word32)
-> ContT b IO (Ptr ("createInfoCount" ::: Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr ("createInfoCount" ::: Word32)
forall a. Ptr a
nullPtr
      vecLen :: Int
vecLen -> do
        let requiredLen :: "createInfoCount" ::: Word32
requiredLen = case (SampleCountFlagBits
rasterizationSamples) of
              SampleCountFlagBits n :: "createInfoCount" ::: Word32
n -> ("createInfoCount" ::: Word32
n ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> "createInfoCount" ::: Word32
forall a. Num a => a -> a -> a
+ 31) ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> "createInfoCount" ::: Word32
forall a. Integral a => a -> a -> a
`quot` 32
        IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ("createInfoCount" ::: Word32
requiredLen ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
vecLen) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
          IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "sampleMask must be either empty or contain enough bits to cover all the sample specified by 'rasterizationSamples'" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
        do
          Ptr ("createInfoCount" ::: Word32)
pPSampleMask' <- ((Ptr ("createInfoCount" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("createInfoCount" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("createInfoCount" ::: Word32) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("createInfoCount" ::: Word32)))
-> ((Ptr ("createInfoCount" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("createInfoCount" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("createInfoCount" ::: Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SampleMask ((Vector ("createInfoCount" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length ((Vector ("createInfoCount" ::: Word32)
sampleMask))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
          IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> ("createInfoCount" ::: Word32) -> IO ())
-> Vector ("createInfoCount" ::: Word32) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "createInfoCount" ::: Word32
e -> Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("createInfoCount" ::: Word32)
pPSampleMask' Ptr ("createInfoCount" ::: Word32)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SampleMask) ("createInfoCount" ::: Word32
e)) ((Vector ("createInfoCount" ::: Word32)
sampleMask))
          Ptr ("createInfoCount" ::: Word32)
-> ContT b IO (Ptr ("createInfoCount" ::: Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr ("createInfoCount" ::: Word32)
 -> ContT b IO (Ptr ("createInfoCount" ::: Word32)))
-> Ptr ("createInfoCount" ::: Word32)
-> ContT b IO (Ptr ("createInfoCount" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
pPSampleMask'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ("createInfoCount" ::: Word32))
-> Ptr ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es)
-> Int -> Ptr (Ptr ("createInfoCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr SampleMask))) Ptr ("createInfoCount" ::: Word32)
pSampleMask''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
alphaToCoverageEnable))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
alphaToOneEnable))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PipelineMultisampleStateCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PipelineMultisampleStateCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_MULTISAMPLE_STATE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PipelineMultisampleStateCreateInfo es, PeekChain es) => FromCStruct (PipelineMultisampleStateCreateInfo es) where
  peekCStruct :: Ptr (PipelineMultisampleStateCreateInfo es)
-> IO (PipelineMultisampleStateCreateInfo es)
peekCStruct p :: Ptr (PipelineMultisampleStateCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PipelineMultisampleStateCreateFlags
flags <- Ptr PipelineMultisampleStateCreateFlags
-> IO PipelineMultisampleStateCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineMultisampleStateCreateFlags ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es)
-> Int -> Ptr PipelineMultisampleStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineMultisampleStateCreateFlags))
    SampleCountFlagBits
rasterizationSamples <- Ptr SampleCountFlagBits -> IO SampleCountFlagBits
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlagBits ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr SampleCountFlagBits))
    Bool32
sampleShadingEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    CFloat
minSampleShading <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr CFloat))
    Ptr ("createInfoCount" ::: Word32)
pSampleMask <- Ptr (Ptr ("createInfoCount" ::: Word32))
-> IO (Ptr ("createInfoCount" ::: Word32))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SampleMask) ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es)
-> Int -> Ptr (Ptr ("createInfoCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr SampleMask)))
    Vector ("createInfoCount" ::: Word32)
pSampleMask' <- if Ptr ("createInfoCount" ::: Word32)
pSampleMask Ptr ("createInfoCount" ::: Word32)
-> Ptr ("createInfoCount" ::: Word32) -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr ("createInfoCount" ::: Word32)
forall a. Ptr a
nullPtr
      then Vector ("createInfoCount" ::: Word32)
-> IO (Vector ("createInfoCount" ::: Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Vector ("createInfoCount" ::: Word32)
forall a. Monoid a => a
mempty
      else Int
-> (Int -> IO ("createInfoCount" ::: Word32))
-> IO (Vector ("createInfoCount" ::: Word32))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (case SampleCountFlagBits
rasterizationSamples of
        SampleCountFlagBits n :: "createInfoCount" ::: Word32
n -> (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "createInfoCount" ::: Word32
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 31) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` 32) (\i :: Int
i -> Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @SampleMask (((Ptr ("createInfoCount" ::: Word32)
pSampleMask) Ptr ("createInfoCount" ::: Word32)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SampleMask)))
    Bool32
alphaToCoverageEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32))
    Bool32
alphaToOneEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (PipelineMultisampleStateCreateInfo es)
p Ptr (PipelineMultisampleStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32))
    PipelineMultisampleStateCreateInfo es
-> IO (PipelineMultisampleStateCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineMultisampleStateCreateInfo es
 -> IO (PipelineMultisampleStateCreateInfo es))
-> PipelineMultisampleStateCreateInfo es
-> IO (PipelineMultisampleStateCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineMultisampleStateCreateFlags
-> SampleCountFlagBits
-> Bool
-> Float
-> Vector ("createInfoCount" ::: Word32)
-> Bool
-> Bool
-> PipelineMultisampleStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineMultisampleStateCreateFlags
-> SampleCountFlagBits
-> Bool
-> Float
-> Vector ("createInfoCount" ::: Word32)
-> Bool
-> Bool
-> PipelineMultisampleStateCreateInfo es
PipelineMultisampleStateCreateInfo
             Chain es
next PipelineMultisampleStateCreateFlags
flags SampleCountFlagBits
rasterizationSamples (Bool32 -> Bool
bool32ToBool Bool32
sampleShadingEnable) ((\(CFloat a :: Float
a) -> Float
a) CFloat
minSampleShading) Vector ("createInfoCount" ::: Word32)
pSampleMask' (Bool32 -> Bool
bool32ToBool Bool32
alphaToCoverageEnable) (Bool32 -> Bool
bool32ToBool Bool32
alphaToOneEnable)

instance es ~ '[] => Zero (PipelineMultisampleStateCreateInfo es) where
  zero :: PipelineMultisampleStateCreateInfo es
zero = Chain es
-> PipelineMultisampleStateCreateFlags
-> SampleCountFlagBits
-> Bool
-> Float
-> Vector ("createInfoCount" ::: Word32)
-> Bool
-> Bool
-> PipelineMultisampleStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineMultisampleStateCreateFlags
-> SampleCountFlagBits
-> Bool
-> Float
-> Vector ("createInfoCount" ::: Word32)
-> Bool
-> Bool
-> PipelineMultisampleStateCreateInfo es
PipelineMultisampleStateCreateInfo
           ()
           PipelineMultisampleStateCreateFlags
forall a. Zero a => a
zero
           SampleCountFlagBits
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Vector ("createInfoCount" ::: Word32)
forall a. Monoid a => a
mempty
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkPipelineColorBlendAttachmentState - Structure specifying a pipeline
-- color blend attachment state
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dualSrcBlend dual source blending>
--     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'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dualSrcBlend dual source blending>
--     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'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dualSrcBlend dual source blending>
--     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'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-dualSrcBlend dual source blending>
--     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'
--
-- -   If either of @colorBlendOp@ or @alphaBlendOp@ is an
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blend-advanced advanced blend operation>,
--     then @colorBlendOp@ /must/ equal @alphaBlendOp@
--
-- -   If
--     'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PhysicalDeviceBlendOperationAdvancedPropertiesEXT'::@advancedBlendIndependentBlend@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE' and @colorBlendOp@ is an
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blend-advanced advanced blend operation>,
--     then @colorBlendOp@ /must/ be the same for all attachments
--
-- -   If
--     'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PhysicalDeviceBlendOperationAdvancedPropertiesEXT'::@advancedBlendIndependentBlend@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE' and @alphaBlendOp@ is an
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blend-advanced advanced blend operation>,
--     then @alphaBlendOp@ /must/ be the same for all attachments
--
-- -   If
--     'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PhysicalDeviceBlendOperationAdvancedPropertiesEXT'::@advancedBlendAllOperations@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', then @colorBlendOp@
--     /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'
--
-- -   If @colorBlendOp@ or @alphaBlendOp@ is an
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blend-advanced advanced blend operation>,
--     then @colorAttachmentCount@ of the subpass this pipeline is compiled
--     against /must/ be less than or equal to
--     'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PhysicalDeviceBlendOperationAdvancedPropertiesEXT'::advancedBlendMaxColorAttachments
--
-- -   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'.
--
-- -   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)
--
-- -   @srcColorBlendFactor@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendFactor.BlendFactor' value
--
-- -   @dstColorBlendFactor@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendFactor.BlendFactor' value
--
-- -   @colorBlendOp@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendOp.BlendOp' value
--
-- -   @srcAlphaBlendFactor@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendFactor.BlendFactor' value
--
-- -   @dstAlphaBlendFactor@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendFactor.BlendFactor' value
--
-- -   @alphaBlendOp@ /must/ be a valid
--     'Vulkan.Core10.Enums.BlendOp.BlendOp' value
--
-- -   @colorWriteMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ColorComponentFlagBits.ColorComponentFlagBits'
--     values
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.BlendFactor.BlendFactor',
-- 'Vulkan.Core10.Enums.BlendOp.BlendOp',
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.ColorComponentFlagBits.ColorComponentFlags',
-- 'PipelineColorBlendStateCreateInfo'
data PipelineColorBlendAttachmentState = PipelineColorBlendAttachmentState
  { -- | @blendEnable@ controls whether blending is enabled for the corresponding
    -- color attachment. If blending is not enabled, the source fragment’s
    -- color for that attachment is passed through unmodified.
    PipelineColorBlendAttachmentState -> Bool
blendEnable :: Bool
  , -- | @srcColorBlendFactor@ selects which blend factor is used to determine
    -- the source factors (Sr,Sg,Sb).
    PipelineColorBlendAttachmentState -> BlendFactor
srcColorBlendFactor :: BlendFactor
  , -- | @dstColorBlendFactor@ selects which blend factor is used to determine
    -- the destination factors (Dr,Dg,Db).
    PipelineColorBlendAttachmentState -> BlendFactor
dstColorBlendFactor :: BlendFactor
  , -- | @colorBlendOp@ selects which blend operation is used to calculate the
    -- RGB values to write to the color attachment.
    PipelineColorBlendAttachmentState -> BlendOp
colorBlendOp :: BlendOp
  , -- | @srcAlphaBlendFactor@ selects which blend factor is used to determine
    -- the source factor Sa.
    PipelineColorBlendAttachmentState -> BlendFactor
srcAlphaBlendFactor :: BlendFactor
  , -- | @dstAlphaBlendFactor@ selects which blend factor is used to determine
    -- the destination factor Da.
    PipelineColorBlendAttachmentState -> BlendFactor
dstAlphaBlendFactor :: BlendFactor
  , -- | @alphaBlendOp@ selects which blend operation is use to calculate the
    -- alpha values to write to the color attachment.
    PipelineColorBlendAttachmentState -> BlendOp
alphaBlendOp :: BlendOp
  , -- | @colorWriteMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.ColorComponentFlagBits.ColorComponentFlagBits'
    -- specifying which of the R, G, B, and\/or A components are enabled for
    -- writing, as described for the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-color-write-mask Color Write Mask>.
    PipelineColorBlendAttachmentState -> ColorComponentFlags
colorWriteMask :: ColorComponentFlags
  }
  deriving (Typeable, PipelineColorBlendAttachmentState
-> PipelineColorBlendAttachmentState -> Bool
(PipelineColorBlendAttachmentState
 -> PipelineColorBlendAttachmentState -> Bool)
-> (PipelineColorBlendAttachmentState
    -> PipelineColorBlendAttachmentState -> Bool)
-> Eq PipelineColorBlendAttachmentState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineColorBlendAttachmentState
-> PipelineColorBlendAttachmentState -> Bool
$c/= :: PipelineColorBlendAttachmentState
-> PipelineColorBlendAttachmentState -> Bool
== :: PipelineColorBlendAttachmentState
-> PipelineColorBlendAttachmentState -> Bool
$c== :: PipelineColorBlendAttachmentState
-> PipelineColorBlendAttachmentState -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineColorBlendAttachmentState)
#endif
deriving instance Show PipelineColorBlendAttachmentState

instance ToCStruct PipelineColorBlendAttachmentState where
  withCStruct :: PipelineColorBlendAttachmentState
-> (Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b
withCStruct x :: PipelineColorBlendAttachmentState
x f :: Ptr PipelineColorBlendAttachmentState -> IO b
f = Int
-> Int -> (Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 4 ((Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b)
-> (Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PipelineColorBlendAttachmentState
p -> Ptr PipelineColorBlendAttachmentState
-> PipelineColorBlendAttachmentState -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineColorBlendAttachmentState
p PipelineColorBlendAttachmentState
x (Ptr PipelineColorBlendAttachmentState -> IO b
f Ptr PipelineColorBlendAttachmentState
p)
  pokeCStruct :: Ptr PipelineColorBlendAttachmentState
-> PipelineColorBlendAttachmentState -> IO b -> IO b
pokeCStruct p :: Ptr PipelineColorBlendAttachmentState
p PipelineColorBlendAttachmentState{..} f :: IO b
f = do
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
blendEnable))
    Ptr BlendFactor -> BlendFactor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr BlendFactor)) (BlendFactor
srcColorBlendFactor)
    Ptr BlendFactor -> BlendFactor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr BlendFactor)) (BlendFactor
dstColorBlendFactor)
    Ptr BlendOp -> BlendOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr BlendOp)) (BlendOp
colorBlendOp)
    Ptr BlendFactor -> BlendFactor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr BlendFactor)) (BlendFactor
srcAlphaBlendFactor)
    Ptr BlendFactor -> BlendFactor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr BlendFactor)) (BlendFactor
dstAlphaBlendFactor)
    Ptr BlendOp -> BlendOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr BlendOp)) (BlendOp
alphaBlendOp)
    Ptr ColorComponentFlags -> ColorComponentFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState
-> Int -> Ptr ColorComponentFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ColorComponentFlags)) (ColorComponentFlags
colorWriteMask)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr PipelineColorBlendAttachmentState -> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineColorBlendAttachmentState
p f :: IO b
f = do
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr BlendFactor -> BlendFactor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr BlendFactor)) (BlendFactor
forall a. Zero a => a
zero)
    Ptr BlendFactor -> BlendFactor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr BlendFactor)) (BlendFactor
forall a. Zero a => a
zero)
    Ptr BlendOp -> BlendOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr BlendOp)) (BlendOp
forall a. Zero a => a
zero)
    Ptr BlendFactor -> BlendFactor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr BlendFactor)) (BlendFactor
forall a. Zero a => a
zero)
    Ptr BlendFactor -> BlendFactor -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr BlendFactor)) (BlendFactor
forall a. Zero a => a
zero)
    Ptr BlendOp -> BlendOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr BlendOp)) (BlendOp
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PipelineColorBlendAttachmentState where
  peekCStruct :: Ptr PipelineColorBlendAttachmentState
-> IO PipelineColorBlendAttachmentState
peekCStruct p :: Ptr PipelineColorBlendAttachmentState
p = do
    Bool32
blendEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Bool32))
    BlendFactor
srcColorBlendFactor <- Ptr BlendFactor -> IO BlendFactor
forall a. Storable a => Ptr a -> IO a
peek @BlendFactor ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr BlendFactor))
    BlendFactor
dstColorBlendFactor <- Ptr BlendFactor -> IO BlendFactor
forall a. Storable a => Ptr a -> IO a
peek @BlendFactor ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr BlendFactor))
    BlendOp
colorBlendOp <- Ptr BlendOp -> IO BlendOp
forall a. Storable a => Ptr a -> IO a
peek @BlendOp ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr BlendOp))
    BlendFactor
srcAlphaBlendFactor <- Ptr BlendFactor -> IO BlendFactor
forall a. Storable a => Ptr a -> IO a
peek @BlendFactor ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr BlendFactor))
    BlendFactor
dstAlphaBlendFactor <- Ptr BlendFactor -> IO BlendFactor
forall a. Storable a => Ptr a -> IO a
peek @BlendFactor ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendFactor
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr BlendFactor))
    BlendOp
alphaBlendOp <- Ptr BlendOp -> IO BlendOp
forall a. Storable a => Ptr a -> IO a
peek @BlendOp ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState -> Int -> Ptr BlendOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr BlendOp))
    ColorComponentFlags
colorWriteMask <- Ptr ColorComponentFlags -> IO ColorComponentFlags
forall a. Storable a => Ptr a -> IO a
peek @ColorComponentFlags ((Ptr PipelineColorBlendAttachmentState
p Ptr PipelineColorBlendAttachmentState
-> Int -> Ptr ColorComponentFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ColorComponentFlags))
    PipelineColorBlendAttachmentState
-> IO PipelineColorBlendAttachmentState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineColorBlendAttachmentState
 -> IO PipelineColorBlendAttachmentState)
-> PipelineColorBlendAttachmentState
-> IO PipelineColorBlendAttachmentState
forall a b. (a -> b) -> a -> b
$ Bool
-> BlendFactor
-> BlendFactor
-> BlendOp
-> BlendFactor
-> BlendFactor
-> BlendOp
-> ColorComponentFlags
-> PipelineColorBlendAttachmentState
PipelineColorBlendAttachmentState
             (Bool32 -> Bool
bool32ToBool Bool32
blendEnable) BlendFactor
srcColorBlendFactor BlendFactor
dstColorBlendFactor BlendOp
colorBlendOp BlendFactor
srcAlphaBlendFactor BlendFactor
dstAlphaBlendFactor BlendOp
alphaBlendOp ColorComponentFlags
colorWriteMask

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

instance Zero PipelineColorBlendAttachmentState where
  zero :: PipelineColorBlendAttachmentState
zero = Bool
-> BlendFactor
-> BlendFactor
-> BlendOp
-> BlendFactor
-> BlendFactor
-> BlendOp
-> ColorComponentFlags
-> PipelineColorBlendAttachmentState
PipelineColorBlendAttachmentState
           Bool
forall a. Zero a => a
zero
           BlendFactor
forall a. Zero a => a
zero
           BlendFactor
forall a. Zero a => a
zero
           BlendOp
forall a. Zero a => a
zero
           BlendFactor
forall a. Zero a => a
zero
           BlendFactor
forall a. Zero a => a
zero
           BlendOp
forall a. Zero a => a
zero
           ColorComponentFlags
forall a. Zero a => a
zero


-- | VkPipelineColorBlendStateCreateInfo - Structure specifying parameters of
-- a newly created pipeline color blend state
--
-- = Description
--
-- Each element of the @pAttachments@ array is a
-- 'PipelineColorBlendAttachmentState' structure specifying per-target
-- blending state for each individual color attachment. If the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-independentBlend independent blending>
-- feature is not enabled on the device, all
-- 'PipelineColorBlendAttachmentState' elements in the @pAttachments@ array
-- /must/ be identical.
--
-- The value of @attachmentCount@ /must/ be greater than the index of all
-- color attachments that are not
-- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' in
-- 'Vulkan.Core10.Pass.SubpassDescription'::@pColorAttachments@ or
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.SubpassDescription2'::@pColorAttachments@
-- for the subpass in which this pipeline is used.
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-independentBlend independent blending>
--     feature is not enabled, all elements of @pAttachments@ /must/ be
--     identical
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-logicOp logic operations>
--     feature is not enabled, @logicOpEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- -   If @logicOpEnable@ is 'Vulkan.Core10.FundamentalTypes.TRUE',
--     @logicOp@ /must/ be a valid 'Vulkan.Core10.Enums.LogicOp.LogicOp'
--     value
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_STATE_CREATE_INFO'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PipelineColorBlendAdvancedStateCreateInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be @0@
--
-- -   If @attachmentCount@ is not @0@, @pAttachments@ /must/ be a valid
--     pointer to an array of @attachmentCount@ valid
--     'PipelineColorBlendAttachmentState' structures
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Core10.Enums.LogicOp.LogicOp',
-- 'PipelineColorBlendAttachmentState',
-- 'Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags.PipelineColorBlendStateCreateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineColorBlendStateCreateInfo (es :: [Type]) = PipelineColorBlendStateCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PipelineColorBlendStateCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    PipelineColorBlendStateCreateInfo es
-> PipelineColorBlendStateCreateFlags
flags :: PipelineColorBlendStateCreateFlags
  , -- | @logicOpEnable@ controls whether to apply
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-logicop Logical Operations>.
    PipelineColorBlendStateCreateInfo es -> Bool
logicOpEnable :: Bool
  , -- | @logicOp@ selects which logical operation to apply.
    PipelineColorBlendStateCreateInfo es -> LogicOp
logicOp :: LogicOp
  , -- | @pAttachments@: is a pointer to an array of per target attachment
    -- states.
    PipelineColorBlendStateCreateInfo es
-> Vector PipelineColorBlendAttachmentState
attachments :: Vector PipelineColorBlendAttachmentState
  , -- | @blendConstants@ is a pointer to an array of four values used as the R,
    -- G, B, and A components of the blend constant that are used in blending,
    -- depending on the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#framebuffer-blendfactors blend factor>.
    PipelineColorBlendStateCreateInfo es
-> (Float, Float, Float, Float)
blendConstants :: (Float, Float, Float, Float)
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineColorBlendStateCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PipelineColorBlendStateCreateInfo es)

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

instance (Extendss PipelineColorBlendStateCreateInfo es, PokeChain es) => ToCStruct (PipelineColorBlendStateCreateInfo es) where
  withCStruct :: PipelineColorBlendStateCreateInfo es
-> (Ptr (PipelineColorBlendStateCreateInfo es) -> IO b) -> IO b
withCStruct x :: PipelineColorBlendStateCreateInfo es
x f :: Ptr (PipelineColorBlendStateCreateInfo es) -> IO b
f = Int
-> Int
-> (Ptr (PipelineColorBlendStateCreateInfo es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((Ptr (PipelineColorBlendStateCreateInfo es) -> IO b) -> IO b)
-> (Ptr (PipelineColorBlendStateCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PipelineColorBlendStateCreateInfo es)
p -> Ptr (PipelineColorBlendStateCreateInfo es)
-> PipelineColorBlendStateCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PipelineColorBlendStateCreateInfo es)
p PipelineColorBlendStateCreateInfo es
x (Ptr (PipelineColorBlendStateCreateInfo es) -> IO b
f Ptr (PipelineColorBlendStateCreateInfo es)
p)
  pokeCStruct :: Ptr (PipelineColorBlendStateCreateInfo es)
-> PipelineColorBlendStateCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (PipelineColorBlendStateCreateInfo es)
p PipelineColorBlendStateCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_STATE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineColorBlendStateCreateFlags
-> PipelineColorBlendStateCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr PipelineColorBlendStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineColorBlendStateCreateFlags)) (PipelineColorBlendStateCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
logicOpEnable))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr LogicOp -> LogicOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es) -> Int -> Ptr LogicOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr LogicOp)) (LogicOp
logicOp)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector PipelineColorBlendAttachmentState -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector PipelineColorBlendAttachmentState -> Int)
-> Vector PipelineColorBlendAttachmentState -> Int
forall a b. (a -> b) -> a -> b
$ (Vector PipelineColorBlendAttachmentState
attachments)) :: Word32))
    Ptr PipelineColorBlendAttachmentState
pPAttachments' <- ((Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineColorBlendAttachmentState)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b)
 -> ContT b IO (Ptr PipelineColorBlendAttachmentState))
-> ((Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineColorBlendAttachmentState)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @PipelineColorBlendAttachmentState ((Vector PipelineColorBlendAttachmentState -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector PipelineColorBlendAttachmentState
attachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32) 4
    (Int -> PipelineColorBlendAttachmentState -> ContT b IO ())
-> Vector PipelineColorBlendAttachmentState -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: PipelineColorBlendAttachmentState
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineColorBlendAttachmentState
-> PipelineColorBlendAttachmentState -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr PipelineColorBlendAttachmentState
pPAttachments' Ptr PipelineColorBlendAttachmentState
-> Int -> Ptr PipelineColorBlendAttachmentState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineColorBlendAttachmentState) (PipelineColorBlendAttachmentState
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector PipelineColorBlendAttachmentState
attachments)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PipelineColorBlendAttachmentState)
-> Ptr PipelineColorBlendAttachmentState -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr (Ptr PipelineColorBlendAttachmentState)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr PipelineColorBlendAttachmentState))) (Ptr PipelineColorBlendAttachmentState
pPAttachments')
    let pBlendConstants' :: Ptr CFloat
pBlendConstants' = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr (FixedArray 4 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (FixedArray 4 CFloat)))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ case ((Float, Float, Float, Float)
blendConstants) of
      (e0 :: Float
e0, e1 :: Float
e1, e2 :: Float
e2, e3 :: Float
e3) -> do
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pBlendConstants' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pBlendConstants' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pBlendConstants' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pBlendConstants' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 56
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PipelineColorBlendStateCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PipelineColorBlendStateCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_STATE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr LogicOp -> LogicOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es) -> Int -> Ptr LogicOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr LogicOp)) (LogicOp
forall a. Zero a => a
zero)
    Ptr PipelineColorBlendAttachmentState
pPAttachments' <- ((Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineColorBlendAttachmentState)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b)
 -> ContT b IO (Ptr PipelineColorBlendAttachmentState))
-> ((Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineColorBlendAttachmentState)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (Ptr PipelineColorBlendAttachmentState -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @PipelineColorBlendAttachmentState ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32) 4
    (Int -> PipelineColorBlendAttachmentState -> ContT b IO ())
-> Vector PipelineColorBlendAttachmentState -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: PipelineColorBlendAttachmentState
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineColorBlendAttachmentState
-> PipelineColorBlendAttachmentState -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr PipelineColorBlendAttachmentState
pPAttachments' Ptr PipelineColorBlendAttachmentState
-> Int -> Ptr PipelineColorBlendAttachmentState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineColorBlendAttachmentState) (PipelineColorBlendAttachmentState
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector PipelineColorBlendAttachmentState
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PipelineColorBlendAttachmentState)
-> Ptr PipelineColorBlendAttachmentState -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr (Ptr PipelineColorBlendAttachmentState)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr PipelineColorBlendAttachmentState))) (Ptr PipelineColorBlendAttachmentState
pPAttachments')
    let pBlendConstants' :: Ptr CFloat
pBlendConstants' = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr (FixedArray 4 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (FixedArray 4 CFloat)))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ case ((Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero)) of
      (e0 :: Float
e0, e1 :: Float
e1, e2 :: Float
e2, e3 :: Float
e3) -> do
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pBlendConstants' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pBlendConstants' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pBlendConstants' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pBlendConstants' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PipelineColorBlendStateCreateInfo es, PeekChain es) => FromCStruct (PipelineColorBlendStateCreateInfo es) where
  peekCStruct :: Ptr (PipelineColorBlendStateCreateInfo es)
-> IO (PipelineColorBlendStateCreateInfo es)
peekCStruct p :: Ptr (PipelineColorBlendStateCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PipelineColorBlendStateCreateFlags
flags <- Ptr PipelineColorBlendStateCreateFlags
-> IO PipelineColorBlendStateCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineColorBlendStateCreateFlags ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr PipelineColorBlendStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineColorBlendStateCreateFlags))
    Bool32
logicOpEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es) -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    LogicOp
logicOp <- Ptr LogicOp -> IO LogicOp
forall a. Storable a => Ptr a -> IO a
peek @LogicOp ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es) -> Int -> Ptr LogicOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr LogicOp))
    "createInfoCount" ::: Word32
attachmentCount <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
    Ptr PipelineColorBlendAttachmentState
pAttachments <- Ptr (Ptr PipelineColorBlendAttachmentState)
-> IO (Ptr PipelineColorBlendAttachmentState)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PipelineColorBlendAttachmentState) ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr (Ptr PipelineColorBlendAttachmentState)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr PipelineColorBlendAttachmentState)))
    Vector PipelineColorBlendAttachmentState
pAttachments' <- Int
-> (Int -> IO PipelineColorBlendAttachmentState)
-> IO (Vector PipelineColorBlendAttachmentState)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "createInfoCount" ::: Word32
attachmentCount) (\i :: Int
i -> Ptr PipelineColorBlendAttachmentState
-> IO PipelineColorBlendAttachmentState
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PipelineColorBlendAttachmentState ((Ptr PipelineColorBlendAttachmentState
pAttachments Ptr PipelineColorBlendAttachmentState
-> Int -> Ptr PipelineColorBlendAttachmentState
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineColorBlendAttachmentState)))
    let pblendConstants :: Ptr CFloat
pblendConstants = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @CFloat ((Ptr (PipelineColorBlendStateCreateInfo es)
p Ptr (PipelineColorBlendStateCreateInfo es)
-> Int -> Ptr (FixedArray 4 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (FixedArray 4 CFloat)))
    CFloat
blendConstants0 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pblendConstants Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr CFloat))
    CFloat
blendConstants1 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pblendConstants Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr CFloat))
    CFloat
blendConstants2 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pblendConstants Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 8 :: Ptr CFloat))
    CFloat
blendConstants3 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pblendConstants Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 12 :: Ptr CFloat))
    PipelineColorBlendStateCreateInfo es
-> IO (PipelineColorBlendStateCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineColorBlendStateCreateInfo es
 -> IO (PipelineColorBlendStateCreateInfo es))
-> PipelineColorBlendStateCreateInfo es
-> IO (PipelineColorBlendStateCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineColorBlendStateCreateFlags
-> Bool
-> LogicOp
-> Vector PipelineColorBlendAttachmentState
-> (Float, Float, Float, Float)
-> PipelineColorBlendStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineColorBlendStateCreateFlags
-> Bool
-> LogicOp
-> Vector PipelineColorBlendAttachmentState
-> (Float, Float, Float, Float)
-> PipelineColorBlendStateCreateInfo es
PipelineColorBlendStateCreateInfo
             Chain es
next PipelineColorBlendStateCreateFlags
flags (Bool32 -> Bool
bool32ToBool Bool32
logicOpEnable) LogicOp
logicOp Vector PipelineColorBlendAttachmentState
pAttachments' ((((\(CFloat a :: Float
a) -> Float
a) CFloat
blendConstants0), ((\(CFloat a :: Float
a) -> Float
a) CFloat
blendConstants1), ((\(CFloat a :: Float
a) -> Float
a) CFloat
blendConstants2), ((\(CFloat a :: Float
a) -> Float
a) CFloat
blendConstants3)))

instance es ~ '[] => Zero (PipelineColorBlendStateCreateInfo es) where
  zero :: PipelineColorBlendStateCreateInfo es
zero = Chain es
-> PipelineColorBlendStateCreateFlags
-> Bool
-> LogicOp
-> Vector PipelineColorBlendAttachmentState
-> (Float, Float, Float, Float)
-> PipelineColorBlendStateCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineColorBlendStateCreateFlags
-> Bool
-> LogicOp
-> Vector PipelineColorBlendAttachmentState
-> (Float, Float, Float, Float)
-> PipelineColorBlendStateCreateInfo es
PipelineColorBlendStateCreateInfo
           ()
           PipelineColorBlendStateCreateFlags
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           LogicOp
forall a. Zero a => a
zero
           Vector PipelineColorBlendAttachmentState
forall a. Monoid a => a
mempty
           (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero)


-- | VkPipelineDynamicStateCreateInfo - Structure specifying parameters of a
-- newly created pipeline dynamic state
--
-- == Valid Usage
--
-- -   Each element of @pDynamicStates@ /must/ be unique
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_DYNAMIC_STATE_CREATE_INFO'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @flags@ /must/ be @0@
--
-- -   If @dynamicStateCount@ is not @0@, @pDynamicStates@ /must/ be a
--     valid pointer to an array of @dynamicStateCount@ valid
--     'Vulkan.Core10.Enums.DynamicState.DynamicState' values
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.DynamicState.DynamicState',
-- 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags.PipelineDynamicStateCreateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineDynamicStateCreateInfo = PipelineDynamicStateCreateInfo
  { -- | @flags@ is reserved for future use.
    PipelineDynamicStateCreateInfo -> PipelineDynamicStateCreateFlags
flags :: PipelineDynamicStateCreateFlags
  , -- | @pDynamicStates@ is a pointer to an array of
    -- 'Vulkan.Core10.Enums.DynamicState.DynamicState' values specifying which
    -- pieces of pipeline state will use the values from dynamic state commands
    -- rather than from pipeline state creation info.
    PipelineDynamicStateCreateInfo -> Vector DynamicState
dynamicStates :: Vector DynamicState
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineDynamicStateCreateInfo)
#endif
deriving instance Show PipelineDynamicStateCreateInfo

instance ToCStruct PipelineDynamicStateCreateInfo where
  withCStruct :: PipelineDynamicStateCreateInfo
-> (Ptr PipelineDynamicStateCreateInfo -> IO b) -> IO b
withCStruct x :: PipelineDynamicStateCreateInfo
x f :: Ptr PipelineDynamicStateCreateInfo -> IO b
f = Int -> Int -> (Ptr PipelineDynamicStateCreateInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr PipelineDynamicStateCreateInfo -> IO b) -> IO b)
-> (Ptr PipelineDynamicStateCreateInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PipelineDynamicStateCreateInfo
p -> Ptr PipelineDynamicStateCreateInfo
-> PipelineDynamicStateCreateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineDynamicStateCreateInfo
p PipelineDynamicStateCreateInfo
x (Ptr PipelineDynamicStateCreateInfo -> IO b
f Ptr PipelineDynamicStateCreateInfo
p)
  pokeCStruct :: Ptr PipelineDynamicStateCreateInfo
-> PipelineDynamicStateCreateInfo -> IO b -> IO b
pokeCStruct p :: Ptr PipelineDynamicStateCreateInfo
p PipelineDynamicStateCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_DYNAMIC_STATE_CREATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineDynamicStateCreateFlags
-> PipelineDynamicStateCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo
-> Int -> Ptr PipelineDynamicStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineDynamicStateCreateFlags)) (PipelineDynamicStateCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector DynamicState -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DynamicState -> Int) -> Vector DynamicState -> Int
forall a b. (a -> b) -> a -> b
$ (Vector DynamicState
dynamicStates)) :: Word32))
    Ptr DynamicState
pPDynamicStates' <- ((Ptr DynamicState -> IO b) -> IO b)
-> ContT b IO (Ptr DynamicState)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DynamicState -> IO b) -> IO b)
 -> ContT b IO (Ptr DynamicState))
-> ((Ptr DynamicState -> IO b) -> IO b)
-> ContT b IO (Ptr DynamicState)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DynamicState -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DynamicState ((Vector DynamicState -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DynamicState
dynamicStates)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> DynamicState -> IO ()) -> Vector DynamicState -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DynamicState
e -> Ptr DynamicState -> DynamicState -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DynamicState
pPDynamicStates' Ptr DynamicState -> Int -> Ptr DynamicState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DynamicState) (DynamicState
e)) (Vector DynamicState
dynamicStates)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr DynamicState) -> Ptr DynamicState -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo -> Int -> Ptr (Ptr DynamicState)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DynamicState))) (Ptr DynamicState
pPDynamicStates')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PipelineDynamicStateCreateInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineDynamicStateCreateInfo
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_DYNAMIC_STATE_CREATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DynamicState
pPDynamicStates' <- ((Ptr DynamicState -> IO b) -> IO b)
-> ContT b IO (Ptr DynamicState)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DynamicState -> IO b) -> IO b)
 -> ContT b IO (Ptr DynamicState))
-> ((Ptr DynamicState -> IO b) -> IO b)
-> ContT b IO (Ptr DynamicState)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr DynamicState -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DynamicState ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> DynamicState -> IO ()) -> Vector DynamicState -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DynamicState
e -> Ptr DynamicState -> DynamicState -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DynamicState
pPDynamicStates' Ptr DynamicState -> Int -> Ptr DynamicState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DynamicState) (DynamicState
e)) (Vector DynamicState
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr DynamicState) -> Ptr DynamicState -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo -> Int -> Ptr (Ptr DynamicState)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DynamicState))) (Ptr DynamicState
pPDynamicStates')
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct PipelineDynamicStateCreateInfo where
  peekCStruct :: Ptr PipelineDynamicStateCreateInfo
-> IO PipelineDynamicStateCreateInfo
peekCStruct p :: Ptr PipelineDynamicStateCreateInfo
p = do
    PipelineDynamicStateCreateFlags
flags <- Ptr PipelineDynamicStateCreateFlags
-> IO PipelineDynamicStateCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineDynamicStateCreateFlags ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo
-> Int -> Ptr PipelineDynamicStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineDynamicStateCreateFlags))
    "createInfoCount" ::: Word32
dynamicStateCount <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr DynamicState
pDynamicStates <- Ptr (Ptr DynamicState) -> IO (Ptr DynamicState)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr DynamicState) ((Ptr PipelineDynamicStateCreateInfo
p Ptr PipelineDynamicStateCreateInfo -> Int -> Ptr (Ptr DynamicState)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr DynamicState)))
    Vector DynamicState
pDynamicStates' <- Int -> (Int -> IO DynamicState) -> IO (Vector DynamicState)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "createInfoCount" ::: Word32
dynamicStateCount) (\i :: Int
i -> Ptr DynamicState -> IO DynamicState
forall a. Storable a => Ptr a -> IO a
peek @DynamicState ((Ptr DynamicState
pDynamicStates Ptr DynamicState -> Int -> Ptr DynamicState
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DynamicState)))
    PipelineDynamicStateCreateInfo -> IO PipelineDynamicStateCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineDynamicStateCreateInfo
 -> IO PipelineDynamicStateCreateInfo)
-> PipelineDynamicStateCreateInfo
-> IO PipelineDynamicStateCreateInfo
forall a b. (a -> b) -> a -> b
$ PipelineDynamicStateCreateFlags
-> Vector DynamicState -> PipelineDynamicStateCreateInfo
PipelineDynamicStateCreateInfo
             PipelineDynamicStateCreateFlags
flags Vector DynamicState
pDynamicStates'

instance Zero PipelineDynamicStateCreateInfo where
  zero :: PipelineDynamicStateCreateInfo
zero = PipelineDynamicStateCreateFlags
-> Vector DynamicState -> PipelineDynamicStateCreateInfo
PipelineDynamicStateCreateInfo
           PipelineDynamicStateCreateFlags
forall a. Zero a => a
zero
           Vector DynamicState
forall a. Monoid a => a
mempty


-- | VkStencilOpState - Structure specifying stencil operation state
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.CompareOp.CompareOp',
-- 'PipelineDepthStencilStateCreateInfo',
-- 'Vulkan.Core10.Enums.StencilOp.StencilOp'
data StencilOpState = StencilOpState
  { -- | @failOp@ is a 'Vulkan.Core10.Enums.StencilOp.StencilOp' value specifying
    -- the action performed on samples that fail the stencil test.
    --
    -- @failOp@ /must/ be a valid 'Vulkan.Core10.Enums.StencilOp.StencilOp'
    -- value
    StencilOpState -> StencilOp
failOp :: StencilOp
  , -- | @passOp@ is a 'Vulkan.Core10.Enums.StencilOp.StencilOp' value specifying
    -- the action performed on samples that pass both the depth and stencil
    -- tests.
    --
    -- @passOp@ /must/ be a valid 'Vulkan.Core10.Enums.StencilOp.StencilOp'
    -- value
    StencilOpState -> StencilOp
passOp :: StencilOp
  , -- | @depthFailOp@ is a 'Vulkan.Core10.Enums.StencilOp.StencilOp' value
    -- specifying the action performed on samples that pass the stencil test
    -- and fail the depth test.
    --
    -- @depthFailOp@ /must/ be a valid
    -- 'Vulkan.Core10.Enums.StencilOp.StencilOp' value
    StencilOpState -> StencilOp
depthFailOp :: StencilOp
  , -- | @compareOp@ is a 'Vulkan.Core10.Enums.CompareOp.CompareOp' value
    -- specifying the comparison operator used in the stencil test.
    --
    -- @compareOp@ /must/ be a valid 'Vulkan.Core10.Enums.CompareOp.CompareOp'
    -- value
    StencilOpState -> CompareOp
compareOp :: CompareOp
  , -- | @compareMask@ selects the bits of the unsigned integer stencil values
    -- participating in the stencil test.
    StencilOpState -> "createInfoCount" ::: Word32
compareMask :: Word32
  , -- | @writeMask@ selects the bits of the unsigned integer stencil values
    -- updated by the stencil test in the stencil framebuffer attachment.
    StencilOpState -> "createInfoCount" ::: Word32
writeMask :: Word32
  , -- | @reference@ is an integer reference value that is used in the unsigned
    -- stencil comparison.
    StencilOpState -> "createInfoCount" ::: Word32
reference :: Word32
  }
  deriving (Typeable, StencilOpState -> StencilOpState -> Bool
(StencilOpState -> StencilOpState -> Bool)
-> (StencilOpState -> StencilOpState -> Bool) -> Eq StencilOpState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StencilOpState -> StencilOpState -> Bool
$c/= :: StencilOpState -> StencilOpState -> Bool
== :: StencilOpState -> StencilOpState -> Bool
$c== :: StencilOpState -> StencilOpState -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (StencilOpState)
#endif
deriving instance Show StencilOpState

instance ToCStruct StencilOpState where
  withCStruct :: StencilOpState -> (Ptr StencilOpState -> IO b) -> IO b
withCStruct x :: StencilOpState
x f :: Ptr StencilOpState -> IO b
f = Int -> Int -> (Ptr StencilOpState -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 28 4 ((Ptr StencilOpState -> IO b) -> IO b)
-> (Ptr StencilOpState -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr StencilOpState
p -> Ptr StencilOpState -> StencilOpState -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr StencilOpState
p StencilOpState
x (Ptr StencilOpState -> IO b
f Ptr StencilOpState
p)
  pokeCStruct :: Ptr StencilOpState -> StencilOpState -> IO b -> IO b
pokeCStruct p :: Ptr StencilOpState
p StencilOpState{..} f :: IO b
f = do
    Ptr StencilOp -> StencilOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr StencilOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StencilOp)) (StencilOp
failOp)
    Ptr StencilOp -> StencilOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr StencilOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr StencilOp)) (StencilOp
passOp)
    Ptr StencilOp -> StencilOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr StencilOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr StencilOp)) (StencilOp
depthFailOp)
    Ptr CompareOp -> CompareOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr CompareOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CompareOp)) (CompareOp
compareOp)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("createInfoCount" ::: Word32
compareMask)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("createInfoCount" ::: Word32
writeMask)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("createInfoCount" ::: Word32
reference)
    IO b
f
  cStructSize :: Int
cStructSize = 28
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr StencilOpState -> IO b -> IO b
pokeZeroCStruct p :: Ptr StencilOpState
p f :: IO b
f = do
    Ptr StencilOp -> StencilOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr StencilOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StencilOp)) (StencilOp
forall a. Zero a => a
zero)
    Ptr StencilOp -> StencilOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr StencilOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr StencilOp)) (StencilOp
forall a. Zero a => a
zero)
    Ptr StencilOp -> StencilOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr StencilOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr StencilOp)) (StencilOp
forall a. Zero a => a
zero)
    Ptr CompareOp -> CompareOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr CompareOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CompareOp)) (CompareOp
forall a. Zero a => a
zero)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct StencilOpState where
  peekCStruct :: Ptr StencilOpState -> IO StencilOpState
peekCStruct p :: Ptr StencilOpState
p = do
    StencilOp
failOp <- Ptr StencilOp -> IO StencilOp
forall a. Storable a => Ptr a -> IO a
peek @StencilOp ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr StencilOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StencilOp))
    StencilOp
passOp <- Ptr StencilOp -> IO StencilOp
forall a. Storable a => Ptr a -> IO a
peek @StencilOp ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr StencilOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr StencilOp))
    StencilOp
depthFailOp <- Ptr StencilOp -> IO StencilOp
forall a. Storable a => Ptr a -> IO a
peek @StencilOp ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr StencilOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr StencilOp))
    CompareOp
compareOp <- Ptr CompareOp -> IO CompareOp
forall a. Storable a => Ptr a -> IO a
peek @CompareOp ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr CompareOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CompareOp))
    "createInfoCount" ::: Word32
compareMask <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "createInfoCount" ::: Word32
writeMask <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    "createInfoCount" ::: Word32
reference <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr StencilOpState
p Ptr StencilOpState -> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    StencilOpState -> IO StencilOpState
forall (f :: * -> *) a. Applicative f => a -> f a
pure (StencilOpState -> IO StencilOpState)
-> StencilOpState -> IO StencilOpState
forall a b. (a -> b) -> a -> b
$ StencilOp
-> StencilOp
-> StencilOp
-> CompareOp
-> ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> StencilOpState
StencilOpState
             StencilOp
failOp StencilOp
passOp StencilOp
depthFailOp CompareOp
compareOp "createInfoCount" ::: Word32
compareMask "createInfoCount" ::: Word32
writeMask "createInfoCount" ::: Word32
reference

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

instance Zero StencilOpState where
  zero :: StencilOpState
zero = StencilOp
-> StencilOp
-> StencilOp
-> CompareOp
-> ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32)
-> StencilOpState
StencilOpState
           StencilOp
forall a. Zero a => a
zero
           StencilOp
forall a. Zero a => a
zero
           StencilOp
forall a. Zero a => a
zero
           CompareOp
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero


-- | VkPipelineDepthStencilStateCreateInfo - Structure specifying parameters
-- of a newly created pipeline depth stencil state
--
-- == Valid Usage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-depthBounds depth bounds testing>
--     feature is not enabled, @depthBoundsTestEnable@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- -   If the @VK_KHR_portability_subset@ extension is enabled, and
--     'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetFeaturesKHR'::@separateStencilMaskRef@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE', and the value of
--     'PipelineDepthStencilStateCreateInfo'::@stencilTestEnable@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE', and the value of
--     'PipelineRasterizationStateCreateInfo'::@cullMode@ is
--     'Vulkan.Core10.Enums.CullModeFlagBits.CULL_MODE_NONE', the value of
--     @reference@ in each of the 'StencilOpState' structs in @front@ and
--     @back@ /must/ be the same.
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_DEPTH_STENCIL_STATE_CREATE_INFO'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @flags@ /must/ be @0@
--
-- -   @depthCompareOp@ /must/ be a valid
--     'Vulkan.Core10.Enums.CompareOp.CompareOp' value
--
-- -   @front@ /must/ be a valid 'StencilOpState' structure
--
-- -   @back@ /must/ be a valid 'StencilOpState' structure
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.CompareOp.CompareOp', 'GraphicsPipelineCreateInfo',
-- 'Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags.PipelineDepthStencilStateCreateFlags',
-- 'StencilOpState', 'Vulkan.Core10.Enums.StructureType.StructureType'
data PipelineDepthStencilStateCreateInfo = PipelineDepthStencilStateCreateInfo
  { -- | @flags@ is reserved for future use.
    PipelineDepthStencilStateCreateInfo
-> PipelineDepthStencilStateCreateFlags
flags :: PipelineDepthStencilStateCreateFlags
  , -- | @depthTestEnable@ controls whether
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-depth depth testing>
    -- is enabled.
    PipelineDepthStencilStateCreateInfo -> Bool
depthTestEnable :: Bool
  , -- | @depthWriteEnable@ controls whether
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-depth-write depth writes>
    -- are enabled when @depthTestEnable@ is
    -- 'Vulkan.Core10.FundamentalTypes.TRUE'. Depth writes are always disabled
    -- when @depthTestEnable@ is 'Vulkan.Core10.FundamentalTypes.FALSE'.
    PipelineDepthStencilStateCreateInfo -> Bool
depthWriteEnable :: Bool
  , -- | @depthCompareOp@ is the comparison operator used in the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-depth depth test>.
    PipelineDepthStencilStateCreateInfo -> CompareOp
depthCompareOp :: CompareOp
  , -- | @depthBoundsTestEnable@ controls whether
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-dbt depth bounds testing>
    -- is enabled.
    PipelineDepthStencilStateCreateInfo -> Bool
depthBoundsTestEnable :: Bool
  , -- | @stencilTestEnable@ controls whether
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-stencil stencil testing>
    -- is enabled.
    PipelineDepthStencilStateCreateInfo -> Bool
stencilTestEnable :: Bool
  , -- | @front@ and @back@ control the parameters of the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-stencil stencil test>.
    PipelineDepthStencilStateCreateInfo -> StencilOpState
front :: StencilOpState
  , -- No documentation found for Nested "VkPipelineDepthStencilStateCreateInfo" "back"
    PipelineDepthStencilStateCreateInfo -> StencilOpState
back :: StencilOpState
  , -- | @minDepthBounds@ is the minimum depth bound used in the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-dbt depth bounds test>.
    PipelineDepthStencilStateCreateInfo -> Float
minDepthBounds :: Float
  , -- | @maxDepthBounds@ is the maximum depth bound used in the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fragops-dbt depth bounds test>.
    PipelineDepthStencilStateCreateInfo -> Float
maxDepthBounds :: Float
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineDepthStencilStateCreateInfo)
#endif
deriving instance Show PipelineDepthStencilStateCreateInfo

instance ToCStruct PipelineDepthStencilStateCreateInfo where
  withCStruct :: PipelineDepthStencilStateCreateInfo
-> (Ptr PipelineDepthStencilStateCreateInfo -> IO b) -> IO b
withCStruct x :: PipelineDepthStencilStateCreateInfo
x f :: Ptr PipelineDepthStencilStateCreateInfo -> IO b
f = Int
-> Int -> (Ptr PipelineDepthStencilStateCreateInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 104 8 ((Ptr PipelineDepthStencilStateCreateInfo -> IO b) -> IO b)
-> (Ptr PipelineDepthStencilStateCreateInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PipelineDepthStencilStateCreateInfo
p -> Ptr PipelineDepthStencilStateCreateInfo
-> PipelineDepthStencilStateCreateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PipelineDepthStencilStateCreateInfo
p PipelineDepthStencilStateCreateInfo
x (Ptr PipelineDepthStencilStateCreateInfo -> IO b
f Ptr PipelineDepthStencilStateCreateInfo
p)
  pokeCStruct :: Ptr PipelineDepthStencilStateCreateInfo
-> PipelineDepthStencilStateCreateInfo -> IO b -> IO b
pokeCStruct p :: Ptr PipelineDepthStencilStateCreateInfo
p PipelineDepthStencilStateCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_DEPTH_STENCIL_STATE_CREATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineDepthStencilStateCreateFlags
-> PipelineDepthStencilStateCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo
-> Int -> Ptr PipelineDepthStencilStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineDepthStencilStateCreateFlags)) (PipelineDepthStencilStateCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthTestEnable))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthWriteEnable))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CompareOp -> CompareOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr CompareOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr CompareOp)) (CompareOp
depthCompareOp)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
depthBoundsTestEnable))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
stencilTestEnable))
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StencilOpState -> StencilOpState -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo
-> Int -> Ptr StencilOpState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr StencilOpState)) (StencilOpState
front) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StencilOpState -> StencilOpState -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo
-> Int -> Ptr StencilOpState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr StencilOpState)) (StencilOpState
back) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
minDepthBounds))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxDepthBounds))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 104
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PipelineDepthStencilStateCreateInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr PipelineDepthStencilStateCreateInfo
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_DEPTH_STENCIL_STATE_CREATE_INFO)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CompareOp -> CompareOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr CompareOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr CompareOp)) (CompareOp
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StencilOpState -> StencilOpState -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo
-> Int -> Ptr StencilOpState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr StencilOpState)) (StencilOpState
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StencilOpState -> StencilOpState -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo
-> Int -> Ptr StencilOpState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr StencilOpState)) (StencilOpState
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct PipelineDepthStencilStateCreateInfo where
  peekCStruct :: Ptr PipelineDepthStencilStateCreateInfo
-> IO PipelineDepthStencilStateCreateInfo
peekCStruct p :: Ptr PipelineDepthStencilStateCreateInfo
p = do
    PipelineDepthStencilStateCreateFlags
flags <- Ptr PipelineDepthStencilStateCreateFlags
-> IO PipelineDepthStencilStateCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineDepthStencilStateCreateFlags ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo
-> Int -> Ptr PipelineDepthStencilStateCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineDepthStencilStateCreateFlags))
    Bool32
depthTestEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Bool32
depthWriteEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    CompareOp
depthCompareOp <- Ptr CompareOp -> IO CompareOp
forall a. Storable a => Ptr a -> IO a
peek @CompareOp ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr CompareOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr CompareOp))
    Bool32
depthBoundsTestEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32))
    Bool32
stencilTestEnable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32))
    StencilOpState
front <- Ptr StencilOpState -> IO StencilOpState
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @StencilOpState ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo
-> Int -> Ptr StencilOpState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr StencilOpState))
    StencilOpState
back <- Ptr StencilOpState -> IO StencilOpState
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @StencilOpState ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo
-> Int -> Ptr StencilOpState
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 68 :: Ptr StencilOpState))
    CFloat
minDepthBounds <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr CFloat))
    CFloat
maxDepthBounds <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr PipelineDepthStencilStateCreateInfo
p Ptr PipelineDepthStencilStateCreateInfo -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 100 :: Ptr CFloat))
    PipelineDepthStencilStateCreateInfo
-> IO PipelineDepthStencilStateCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineDepthStencilStateCreateInfo
 -> IO PipelineDepthStencilStateCreateInfo)
-> PipelineDepthStencilStateCreateInfo
-> IO PipelineDepthStencilStateCreateInfo
forall a b. (a -> b) -> a -> b
$ PipelineDepthStencilStateCreateFlags
-> Bool
-> Bool
-> CompareOp
-> Bool
-> Bool
-> StencilOpState
-> StencilOpState
-> Float
-> Float
-> PipelineDepthStencilStateCreateInfo
PipelineDepthStencilStateCreateInfo
             PipelineDepthStencilStateCreateFlags
flags (Bool32 -> Bool
bool32ToBool Bool32
depthTestEnable) (Bool32 -> Bool
bool32ToBool Bool32
depthWriteEnable) CompareOp
depthCompareOp (Bool32 -> Bool
bool32ToBool Bool32
depthBoundsTestEnable) (Bool32 -> Bool
bool32ToBool Bool32
stencilTestEnable) StencilOpState
front StencilOpState
back ((\(CFloat a :: Float
a) -> Float
a) CFloat
minDepthBounds) ((\(CFloat a :: Float
a) -> Float
a) CFloat
maxDepthBounds)

instance Zero PipelineDepthStencilStateCreateInfo where
  zero :: PipelineDepthStencilStateCreateInfo
zero = PipelineDepthStencilStateCreateFlags
-> Bool
-> Bool
-> CompareOp
-> Bool
-> Bool
-> StencilOpState
-> StencilOpState
-> Float
-> Float
-> PipelineDepthStencilStateCreateInfo
PipelineDepthStencilStateCreateInfo
           PipelineDepthStencilStateCreateFlags
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           CompareOp
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           StencilOpState
forall a. Zero a => a
zero
           StencilOpState
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero
           Float
forall a. Zero a => a
zero


-- | VkGraphicsPipelineCreateInfo - Structure specifying parameters of a
-- newly created graphics pipeline
--
-- = Description
--
-- The parameters @basePipelineHandle@ and @basePipelineIndex@ are
-- described in more detail in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipelines-pipeline-derivatives Pipeline Derivatives>.
--
-- If any shader stage fails to compile, the compile log will be reported
-- back to the application, and
-- 'Vulkan.Core10.Enums.Result.ERROR_INVALID_SHADER_NV' will be generated.
--
-- == Valid Usage
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineIndex@ is -1, @basePipelineHandle@ /must/ be
--     a valid handle to a graphics 'Vulkan.Core10.Handles.Pipeline'
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineHandle@ is
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @basePipelineIndex@ /must/
--     be a valid index into the calling command’s @pCreateInfos@ parameter
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineIndex@ is not -1, @basePipelineHandle@ /must/
--     be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineHandle@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @basePipelineIndex@ /must/
--     be -1
--
-- -   The @stage@ member of each element of @pStages@ /must/ be unique
--
-- -   The geometric shader stages provided in @pStages@ /must/ be either
--     from the mesh shading pipeline (@stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TASK_BIT_NV'
--     or
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_NV')
--     or from the primitive shading pipeline (@stage@ is
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT',
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_CONTROL_BIT',
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_TESSELLATION_EVALUATION_BIT',
--     or
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_GEOMETRY_BIT')
--
-- -   The @stage@ member of one element of @pStages@ /must/ be either
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_VERTEX_BIT' or
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MESH_BIT_NV'
--
-- -   The @stage@ member of each element of @pStages@ /must/ not be
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_COMPUTE_BIT'
--
-- -   If @pStages@ includes a tessellation control shader stage, it /must/
--     include a tessellation evaluation shader stage
--
-- -   If @pStages@ includes a tessellation evaluation shader stage, it
--     /must/ include a tessellation control shader stage
--
-- -   If @pStages@ includes a tessellation control shader stage and a
--     tessellation evaluation shader stage, @pTessellationState@ /must/ be
--     a valid pointer to a valid 'PipelineTessellationStateCreateInfo'
--     structure
--
-- -   If @pStages@ includes tessellation shader stages, the shader code of
--     at least one stage /must/ contain an @OpExecutionMode@ instruction
--     that specifies the type of subdivision in the pipeline
--
-- -   If @pStages@ includes tessellation shader stages, and the shader
--     code of both stages contain an @OpExecutionMode@ instruction that
--     specifies the type of subdivision in the pipeline, they /must/ both
--     specify the same subdivision mode
--
-- -   If @pStages@ includes tessellation shader stages, the shader code of
--     at least one stage /must/ contain an @OpExecutionMode@ instruction
--     that specifies the output patch size in the pipeline
--
-- -   If @pStages@ includes tessellation shader stages, and the shader
--     code of both contain an @OpExecutionMode@ instruction that specifies
--     the out patch size in the pipeline, they /must/ both specify the
--     same patch size
--
-- -   If @pStages@ includes tessellation shader stages, the @topology@
--     member of @pInputAssembly@ /must/ be
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_PATCH_LIST'
--
-- -   If the @topology@ member of @pInputAssembly@ is
--     'Vulkan.Core10.Enums.PrimitiveTopology.PRIMITIVE_TOPOLOGY_PATCH_LIST',
--     @pStages@ /must/ include tessellation shader stages
--
-- -   If @pStages@ includes a geometry shader stage, and does not include
--     any tessellation shader stages, its shader code /must/ contain an
--     @OpExecutionMode@ instruction that specifies an input primitive type
--     that is
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-geometry-execution compatible>
--     with the primitive topology specified in @pInputAssembly@
--
-- -   If @pStages@ includes a geometry shader stage, and also includes
--     tessellation shader stages, its shader code /must/ contain an
--     @OpExecutionMode@ instruction that specifies an input primitive type
--     that is
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-geometry-execution compatible>
--     with the primitive topology that is output by the tessellation
--     stages
--
-- -   If @pStages@ includes a fragment shader stage and a geometry shader
--     stage, and the fragment shader code reads from an input variable
--     that is decorated with @PrimitiveID@, then the geometry shader code
--     /must/ write to a matching output variable, decorated with
--     @PrimitiveID@, in all execution paths
--
-- -   If @pStages@ includes a fragment shader stage, its shader code
--     /must/ not read from any input attachment that is defined as
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' in @subpass@
--
-- -   The shader code for the entry points identified by @pStages@, and
--     the rest of the state identified by this structure /must/ adhere to
--     the pipeline linking rules described in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces Shader Interfaces>
--     chapter
--
-- -   If rasterization is not disabled and @subpass@ uses a depth\/stencil
--     attachment in @renderPass@ that has a layout of
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL'
--     in the 'Vulkan.Core10.Pass.AttachmentReference' defined by
--     @subpass@, the @depthWriteEnable@ member of @pDepthStencilState@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- -   If rasterization is not disabled and @subpass@ uses a depth\/stencil
--     attachment in @renderPass@ that has a layout of
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL'
--     in the 'Vulkan.Core10.Pass.AttachmentReference' defined by
--     @subpass@, the @failOp@, @passOp@ and @depthFailOp@ members of each
--     of the @front@ and @back@ members of @pDepthStencilState@ /must/ be
--     'Vulkan.Core10.Enums.StencilOp.STENCIL_OP_KEEP'
--
-- -   If rasterization is not disabled and the subpass uses color
--     attachments, then for each color attachment in the subpass the
--     @blendEnable@ member of the corresponding element of the
--     @pAttachment@ member of @pColorBlendState@ /must/ be
--     'Vulkan.Core10.FundamentalTypes.FALSE' if the attached image’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-format-features format features>
--     does not contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT'
--
-- -   If rasterization is not disabled and the subpass uses color
--     attachments, the @attachmentCount@ member of @pColorBlendState@
--     /must/ be equal to the @colorAttachmentCount@ used to create
--     @subpass@
--
-- -   If no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT' or
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT',
--     the @pViewports@ member of @pViewportState@ /must/ be a valid
--     pointer to an array of @pViewportState->viewportCount@ valid
--     'Viewport' structures
--
-- -   If no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR' or
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT',
--     the @pScissors@ member of @pViewportState@ /must/ be a valid pointer
--     to an array of @pViewportState->scissorCount@
--     'Vulkan.Core10.FundamentalTypes.Rect2D' structures
--
-- -   If the wide lines feature is not enabled, and no element of the
--     @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_WIDTH', the
--     @lineWidth@ member of @pRasterizationState@ /must/ be @1.0@
--
-- -   If the @rasterizerDiscardEnable@ member of @pRasterizationState@ is
--     'Vulkan.Core10.FundamentalTypes.FALSE', @pViewportState@ /must/ be a
--     valid pointer to a valid 'PipelineViewportStateCreateInfo' structure
--
-- -   If the @rasterizerDiscardEnable@ member of @pRasterizationState@ is
--     'Vulkan.Core10.FundamentalTypes.FALSE', @pMultisampleState@ /must/
--     be a valid pointer to a valid 'PipelineMultisampleStateCreateInfo'
--     structure
--
-- -   If the @rasterizerDiscardEnable@ member of @pRasterizationState@ is
--     'Vulkan.Core10.FundamentalTypes.FALSE', and @subpass@ uses a
--     depth\/stencil attachment, @pDepthStencilState@ /must/ be a valid
--     pointer to a valid 'PipelineDepthStencilStateCreateInfo' structure
--
-- -   If the @rasterizerDiscardEnable@ member of @pRasterizationState@ is
--     'Vulkan.Core10.FundamentalTypes.FALSE', and @subpass@ uses color
--     attachments, @pColorBlendState@ /must/ be a valid pointer to a valid
--     'PipelineColorBlendStateCreateInfo' structure
--
-- -   If the @rasterizerDiscardEnable@ member of @pRasterizationState@ is
--     'Vulkan.Core10.FundamentalTypes.FALSE',
--     @pColorBlendState->attachmentCount@ /must/ be greater than the index
--     of all color attachments that are not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' for the @subpass@
--     index in @renderPass@
--
-- -   If the depth bias clamping feature is not enabled, no element of the
--     @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BIAS', and the
--     @depthBiasEnable@ member of @pRasterizationState@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE', the @depthBiasClamp@ member
--     of @pRasterizationState@ /must/ be @0.0@
--
-- -   If the @VK_EXT_depth_range_unrestricted@ extension is not enabled
--     and no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS', and
--     the @depthBoundsTestEnable@ member of @pDepthStencilState@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE', the @minDepthBounds@ and
--     @maxDepthBounds@ members of @pDepthStencilState@ /must/ be between
--     @0.0@ and @1.0@, inclusive
--
-- -   If no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT',
--     and the @sampleLocationsEnable@ member of a
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'
--     structure included in the @pNext@ chain of @pMultisampleState@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE',
--     @sampleLocationsInfo.sampleLocationGridSize.width@ /must/ evenly
--     divide
--     'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.width@
--     as returned by
--     'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT'
--     with a @samples@ parameter equaling @rasterizationSamples@
--
-- -   If no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT',
--     and the @sampleLocationsEnable@ member of a
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'
--     structure included in the @pNext@ chain of @pMultisampleState@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE',
--     @sampleLocationsInfo.sampleLocationGridSize.height@ /must/ evenly
--     divide
--     'Vulkan.Extensions.VK_EXT_sample_locations.MultisamplePropertiesEXT'::@sampleLocationGridSize.height@
--     as returned by
--     'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT'
--     with a @samples@ parameter equaling @rasterizationSamples@
--
-- -   If no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT',
--     and the @sampleLocationsEnable@ member of a
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'
--     structure included in the @pNext@ chain of @pMultisampleState@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE',
--     @sampleLocationsInfo.sampleLocationsPerPixel@ /must/ equal
--     @rasterizationSamples@
--
-- -   If the @sampleLocationsEnable@ member of a
--     'Vulkan.Extensions.VK_EXT_sample_locations.PipelineSampleLocationsStateCreateInfoEXT'
--     structure included in the @pNext@ chain of @pMultisampleState@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE', the fragment shader code
--     /must/ not statically use the extended instruction
--     @InterpolateAtSample@
--
-- -   @layout@ /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-pipelinelayout-consistency consistent>
--     with all shaders specified in @pStages@
--
-- -   If neither the @VK_AMD_mixed_attachment_samples@ nor the
--     @VK_NV_framebuffer_mixed_samples@ extensions are enabled, and if
--     @subpass@ uses color and\/or depth\/stencil attachments, then the
--     @rasterizationSamples@ member of @pMultisampleState@ /must/ be the
--     same as the sample count for those subpass attachments
--
-- -   If the @VK_AMD_mixed_attachment_samples@ extension is enabled, and
--     if @subpass@ uses color and\/or depth\/stencil attachments, then the
--     @rasterizationSamples@ member of @pMultisampleState@ /must/ equal
--     the maximum of the sample counts of those subpass attachments
--
-- -   If the @VK_NV_framebuffer_mixed_samples@ extension is enabled, and
--     if @subpass@ has a depth\/stencil attachment and depth test, stencil
--     test, or depth bounds test are enabled, then the
--     @rasterizationSamples@ member of @pMultisampleState@ /must/ be the
--     same as the sample count of the depth\/stencil attachment
--
-- -   If the @VK_NV_framebuffer_mixed_samples@ extension is enabled, and
--     if @subpass@ has any color attachments, then the
--     @rasterizationSamples@ member of @pMultisampleState@ /must/ be
--     greater than or equal to the sample count for those subpass
--     attachments
--
-- -   If the @VK_NV_coverage_reduction_mode@ extension is enabled, the
--     coverage reduction mode specified by
--     'Vulkan.Extensions.VK_NV_coverage_reduction_mode.PipelineCoverageReductionStateCreateInfoNV'::@coverageReductionMode@,
--     the @rasterizationSamples@ member of @pMultisampleState@ and the
--     sample counts for the color and depth\/stencil attachments (if the
--     subpass has them) /must/ be a valid combination returned by
--     'Vulkan.Extensions.VK_NV_coverage_reduction_mode.getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV'
--
-- -   If @subpass@ does not use any color and\/or depth\/stencil
--     attachments, then the @rasterizationSamples@ member of
--     @pMultisampleState@ /must/ follow the rules for a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-noattachments zero-attachment subpass>
--
-- -   @subpass@ /must/ be a valid subpass within @renderPass@
--
-- -   If the @renderPass@ has multiview enabled and @subpass@ has more
--     than one bit set in the view mask and @multiviewTessellationShader@
--     is not enabled, then @pStages@ /must/ not include tessellation
--     shaders
--
-- -   If the @renderPass@ has multiview enabled and @subpass@ has more
--     than one bit set in the view mask and @multiviewGeometryShader@ is
--     not enabled, then @pStages@ /must/ not include a geometry shader
--
-- -   If the @renderPass@ has multiview enabled and @subpass@ has more
--     than one bit set in the view mask, shaders in the pipeline /must/
--     not write to the @Layer@ built-in output
--
-- -   If the @renderPass@ has multiview enabled, then all shaders /must/
--     not include variables decorated with the @Layer@ built-in decoration
--     in their interfaces
--
-- -   @flags@ /must/ not contain the
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.PIPELINE_CREATE_DISPATCH_BASE'
--     flag
--
-- -   If @pStages@ includes a fragment shader stage and an input
--     attachment was referenced by an @aspectMask@ at @renderPass@
--     creation time, its shader code /must/ only read from the aspects
--     that were specified for that input attachment
--
-- -   The number of resources in @layout@ accessible to each shader stage
--     that is used by the pipeline /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageResources@
--
-- -   If no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_W_SCALING_NV',
--     and the @viewportWScalingEnable@ member of a
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'
--     structure, included in the @pNext@ chain of @pViewportState@, is
--     'Vulkan.Core10.FundamentalTypes.TRUE', the @pViewportWScalings@
--     member of the
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'
--     /must/ be a pointer to an array of
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.PipelineViewportWScalingStateCreateInfoNV'::@viewportCount@
--     valid
--     'Vulkan.Extensions.VK_NV_clip_space_w_scaling.ViewportWScalingNV'
--     structures
--
-- -   If no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV',
--     and if @pViewportState->pNext@ chain includes a
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PipelineViewportExclusiveScissorStateCreateInfoNV'
--     structure, and if its @exclusiveScissorCount@ member is not @0@,
--     then its @pExclusiveScissors@ member /must/ be a valid pointer to an
--     array of @exclusiveScissorCount@
--     'Vulkan.Core10.FundamentalTypes.Rect2D' structures
--
-- -   If no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV',
--     and if @pViewportState->pNext@ chain includes a
--     'Vulkan.Extensions.VK_NV_shading_rate_image.PipelineViewportShadingRateImageStateCreateInfoNV'
--     structure, then its @pShadingRatePalettes@ member /must/ be a valid
--     pointer to an array of @viewportCount@ valid
--     'Vulkan.Extensions.VK_NV_shading_rate_image.ShadingRatePaletteNV'
--     structures
--
-- -   If no element of the @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DISCARD_RECTANGLE_EXT',
--     and if @pNext@ chain includes a
--     'Vulkan.Extensions.VK_EXT_discard_rectangles.PipelineDiscardRectangleStateCreateInfoEXT'
--     structure, and if its @discardRectangleCount@ member is not @0@,
--     then its @pDiscardRectangles@ member /must/ be a valid pointer to an
--     array of @discardRectangleCount@
--     'Vulkan.Core10.FundamentalTypes.Rect2D' structures
--
-- -   If @pStages@ includes a vertex shader stage, @pVertexInputState@
--     /must/ be a valid pointer to a valid
--     'PipelineVertexInputStateCreateInfo' structure
--
-- -   If @pStages@ includes a vertex shader stage, @pInputAssemblyState@
--     /must/ be a valid pointer to a valid
--     'PipelineInputAssemblyStateCreateInfo' structure
--
-- -   The @Xfb@ execution mode /can/ be specified by only one shader stage
--     in @pStages@
--
-- -   If any shader stage in @pStages@ specifies @Xfb@ execution mode it
--     /must/ be the last vertex processing stage
--
-- -   If a
--     'Vulkan.Extensions.VK_EXT_transform_feedback.PipelineRasterizationStateStreamCreateInfoEXT'::@rasterizationStream@
--     value other than zero is specified, all variables in the output
--     interface of the entry point being compiled decorated with
--     @Position@, @PointSize@, @ClipDistance@, or @CullDistance@ /must/
--     all be decorated with identical @Stream@ values that match the
--     @rasterizationStream@
--
-- -   If
--     'Vulkan.Extensions.VK_EXT_transform_feedback.PipelineRasterizationStateStreamCreateInfoEXT'::@rasterizationStream@
--     is zero, or not specified, all variables in the output interface of
--     the entry point being compiled decorated with @Position@,
--     @PointSize@, @ClipDistance@, or @CullDistance@ /must/ all be
--     decorated with a @Stream@ value of zero, or /must/ not specify the
--     @Stream@ decoration
--
-- -   If the last vertex processing stage is a geometry shader, and that
--     geometry shader uses the @GeometryStreams@ capability, then
--     'Vulkan.Extensions.VK_EXT_transform_feedback.PhysicalDeviceTransformFeedbackFeaturesEXT'::@geometryStreams@
--     feature /must/ be enabled
--
-- -   If there are any mesh shader stages in the pipeline there /must/ not
--     be any shader stage in the pipeline with a @Xfb@ execution mode
--
-- -   If the @lineRasterizationMode@ member of a
--     'Vulkan.Extensions.VK_EXT_line_rasterization.PipelineRasterizationLineStateCreateInfoEXT'
--     structure included in the @pNext@ chain of @pRasterizationState@ is
--     'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_BRESENHAM_EXT'
--     or
--     'Vulkan.Extensions.VK_EXT_line_rasterization.LINE_RASTERIZATION_MODE_RECTANGULAR_SMOOTH_EXT'
--     and if rasterization is enabled, then the @alphaToCoverageEnable@,
--     @alphaToOneEnable@, and @sampleShadingEnable@ members of
--     @pMultisampleState@ /must/ all be
--     'Vulkan.Core10.FundamentalTypes.FALSE'
--
-- -   If the @stippledLineEnable@ member of
--     'Vulkan.Extensions.VK_EXT_line_rasterization.PipelineRasterizationLineStateCreateInfoEXT'
--     is 'Vulkan.Core10.FundamentalTypes.TRUE' and no element of the
--     @pDynamicStates@ member of @pDynamicState@ is
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_LINE_STIPPLE_EXT',
--     then the @lineStippleFactor@ member of
--     'Vulkan.Extensions.VK_EXT_line_rasterization.PipelineRasterizationLineStateCreateInfoEXT'
--     /must/ be in the range [1,256]
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_LIBRARY_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR'
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-extendedDynamicState extendedDynamicState>
--     feature is not enabled, there /must/ be no element of the
--     @pDynamicStates@ member of @pDynamicState@ set to
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_CULL_MODE_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRONT_FACE_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT',
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT',
--     or 'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_STENCIL_OP_EXT'
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     is included in the @pDynamicStates@ array then @viewportCount@
--     /must/ be zero
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     is included in the @pDynamicStates@ array then @scissorCount@ /must/
--     be zero
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     is included in the @pDynamicStates@ array then
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT' /must/ not
--     be present
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT'
--     is included in the @pDynamicStates@ array then
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_SCISSOR' /must/ not
--     be present
--
-- -   If @flags@ includes
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV',
--     then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-deviceGeneratedCommands ::deviceGeneratedCommands>
--     feature /must/ be enabled
--
-- -   If @flags@ includes
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV',
--     then all stages /must/ not specify @Xfb@ execution mode
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineCreationCacheControl pipelineCreationCacheControl>
--     feature is not enabled, @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT'
--     or
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT'
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@,
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::fragmentSize.width
--     /must/ be greater than or equal to @1@
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@,
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::fragmentSize.height
--     /must/ be greater than or equal to @1@
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@,
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::fragmentSize.width
--     /must/ be a power-of-two value
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@,
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::fragmentSize.height
--     /must/ be a power-of-two value
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@,
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::fragmentSize.width
--     /must/ be less than or equal to @4@
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@,
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::fragmentSize.height
--     /must/ be less than or equal to @4@
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@, and the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineFragmentShadingRate pipelineFragmentShadingRate feature>
--     is not enabled,
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::fragmentSize.width
--     and
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::fragmentSize.height
--     /must/ both be equal to @1@
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@, and the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#feature-primitiveFragmentShadingRate primitiveFragmentShadingRate feature>
--     is not enabled,
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::@combinerOps@[0]
--     /must/ be
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FRAGMENT_SHADING_RATE_COMBINER_OP_KEEP_KHR'
--
-- -   If
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@, and the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#feature-attachmentFragmentShadingRate attachmentFragmentShadingRate feature>
--     is not enabled,
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::@combinerOps@[1]
--     /must/ be
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FRAGMENT_SHADING_RATE_COMBINER_OP_KEEP_KHR'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports>
--     limit is not supported,
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT'
--     is not included in @pDynamicState@->@pDynamicStates@, and
--     'PipelineViewportStateCreateInfo'::@viewportCount@ is greater than
--     @1@, entry points specified in @pStages@ /must/ not write to the
--     @PrimitiveShadingRateKHR@ built-in
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports>
--     limit is not supported, and entry points specified in @pStages@
--     write to the @ViewportIndex@ built-in, they /must/ not also write to
--     the @PrimitiveShadingRateKHR@ built-in
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-primitiveFragmentShadingRateWithMultipleViewports primitiveFragmentShadingRateWithMultipleViewports>
--     limit is not supported, and entry points specified in @pStages@
--     write to the @ViewportMaskNV@ built-in, they /must/ not also write
--     to the @PrimitiveShadingRateKHR@ built-in
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-fragmentShadingRateNonTrivialCombinerOps fragmentShadingRateNonTrivialCombinerOps>
--     limit is not supported and
--     'Vulkan.Core10.Enums.DynamicState.DYNAMIC_STATE_FRAGMENT_SHADING_RATE_KHR'
--     is not included in @pDynamicState@->@pDynamicStates@, elements of
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR'::@combinerOps@
--     /must/ be
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FRAGMENT_SHADING_RATE_COMBINER_OP_KEEP_KHR'
--     or
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FRAGMENT_SHADING_RATE_COMBINER_OP_REPLACE_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_GRAPHICS_PIPELINE_CREATE_INFO'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Extensions.VK_NV_device_generated_commands.GraphicsPipelineShaderGroupsCreateInfoNV',
--     'Vulkan.Extensions.VK_AMD_pipeline_compiler_control.PipelineCompilerControlCreateInfoAMD',
--     'Vulkan.Extensions.VK_EXT_pipeline_creation_feedback.PipelineCreationFeedbackCreateInfoEXT',
--     'Vulkan.Extensions.VK_EXT_discard_rectangles.PipelineDiscardRectangleStateCreateInfoEXT',
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PipelineFragmentShadingRateStateCreateInfoKHR',
--     or
--     'Vulkan.Extensions.VK_NV_representative_fragment_test.PipelineRepresentativeFragmentTestStateCreateInfoNV'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlagBits'
--     values
--
-- -   @pStages@ /must/ be a valid pointer to an array of @stageCount@
--     valid 'PipelineShaderStageCreateInfo' structures
--
-- -   @pRasterizationState@ /must/ be a valid pointer to a valid
--     'PipelineRasterizationStateCreateInfo' structure
--
-- -   If @pDynamicState@ is not @NULL@, @pDynamicState@ /must/ be a valid
--     pointer to a valid 'PipelineDynamicStateCreateInfo' structure
--
-- -   @layout@ /must/ be a valid 'Vulkan.Core10.Handles.PipelineLayout'
--     handle
--
-- -   @renderPass@ /must/ be a valid 'Vulkan.Core10.Handles.RenderPass'
--     handle
--
-- -   @stageCount@ /must/ be greater than @0@
--
-- -   Each of @basePipelineHandle@, @layout@, and @renderPass@ that are
--     valid handles of non-ignored parameters /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Pipeline', 'PipelineColorBlendStateCreateInfo',
-- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlags',
-- 'PipelineDepthStencilStateCreateInfo', 'PipelineDynamicStateCreateInfo',
-- 'PipelineInputAssemblyStateCreateInfo',
-- 'Vulkan.Core10.Handles.PipelineLayout',
-- 'PipelineMultisampleStateCreateInfo',
-- 'PipelineRasterizationStateCreateInfo', 'PipelineShaderStageCreateInfo',
-- 'PipelineTessellationStateCreateInfo',
-- 'PipelineVertexInputStateCreateInfo', 'PipelineViewportStateCreateInfo',
-- 'Vulkan.Core10.Handles.RenderPass',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'createGraphicsPipelines'
data GraphicsPipelineCreateInfo (es :: [Type]) = GraphicsPipelineCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    GraphicsPipelineCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlagBits'
    -- specifying how the pipeline will be generated.
    GraphicsPipelineCreateInfo es -> PipelineCreateFlags
flags :: PipelineCreateFlags
  , -- | @pStages@ is a pointer to an array of @stageCount@
    -- 'PipelineShaderStageCreateInfo' structures describing the set of the
    -- shader stages to be included in the graphics pipeline.
    GraphicsPipelineCreateInfo es
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
stages :: Vector (SomeStruct PipelineShaderStageCreateInfo)
  , -- | @pVertexInputState@ is a pointer to a
    -- 'PipelineVertexInputStateCreateInfo' structure. It is ignored if the
    -- pipeline includes a mesh shader stage.
    GraphicsPipelineCreateInfo es
-> Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
vertexInputState :: Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
  , -- | @pInputAssemblyState@ is a pointer to a
    -- 'PipelineInputAssemblyStateCreateInfo' structure which determines input
    -- assembly behavior, as described in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#drawing Drawing Commands>.
    -- It is ignored if the pipeline includes a mesh shader stage.
    GraphicsPipelineCreateInfo es
-> Maybe PipelineInputAssemblyStateCreateInfo
inputAssemblyState :: Maybe PipelineInputAssemblyStateCreateInfo
  , -- | @pTessellationState@ is a pointer to a
    -- 'PipelineTessellationStateCreateInfo' structure, and is ignored if the
    -- pipeline does not include a tessellation control shader stage and
    -- tessellation evaluation shader stage.
    GraphicsPipelineCreateInfo es
-> Maybe (SomeStruct PipelineTessellationStateCreateInfo)
tessellationState :: Maybe (SomeStruct PipelineTessellationStateCreateInfo)
  , -- | @pViewportState@ is a pointer to a 'PipelineViewportStateCreateInfo'
    -- structure, and is ignored if the pipeline has rasterization disabled.
    GraphicsPipelineCreateInfo es
-> Maybe (SomeStruct PipelineViewportStateCreateInfo)
viewportState :: Maybe (SomeStruct PipelineViewportStateCreateInfo)
  , -- | @pRasterizationState@ is a pointer to a
    -- 'PipelineRasterizationStateCreateInfo' structure.
    GraphicsPipelineCreateInfo es
-> SomeStruct PipelineRasterizationStateCreateInfo
rasterizationState :: SomeStruct PipelineRasterizationStateCreateInfo
  , -- | @pMultisampleState@ is a pointer to a
    -- 'PipelineMultisampleStateCreateInfo' structure, and is ignored if the
    -- pipeline has rasterization disabled.
    GraphicsPipelineCreateInfo es
-> Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
multisampleState :: Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
  , -- | @pDepthStencilState@ is a pointer to a
    -- 'PipelineDepthStencilStateCreateInfo' structure, and is ignored if the
    -- pipeline has rasterization disabled or if the subpass of the render pass
    -- the pipeline is created against does not use a depth\/stencil
    -- attachment.
    GraphicsPipelineCreateInfo es
-> Maybe PipelineDepthStencilStateCreateInfo
depthStencilState :: Maybe PipelineDepthStencilStateCreateInfo
  , -- | @pColorBlendState@ is a pointer to a 'PipelineColorBlendStateCreateInfo'
    -- structure, and is ignored if the pipeline has rasterization disabled or
    -- if the subpass of the render pass the pipeline is created against does
    -- not use any color attachments.
    GraphicsPipelineCreateInfo es
-> Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
colorBlendState :: Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
  , -- | @pDynamicState@ is a pointer to a 'PipelineDynamicStateCreateInfo'
    -- structure, and is used to indicate which properties of the pipeline
    -- state object are dynamic and /can/ be changed independently of the
    -- pipeline state. This /can/ be @NULL@, which means no state in the
    -- pipeline is considered dynamic.
    GraphicsPipelineCreateInfo es
-> Maybe PipelineDynamicStateCreateInfo
dynamicState :: Maybe PipelineDynamicStateCreateInfo
  , -- | @layout@ is the description of binding locations used by both the
    -- pipeline and descriptor sets used with the pipeline.
    GraphicsPipelineCreateInfo es -> PipelineLayout
layout :: PipelineLayout
  , -- | @renderPass@ is a handle to a render pass object describing the
    -- environment in which the pipeline will be used; the pipeline /must/ only
    -- be used with an instance of any render pass compatible with the one
    -- provided. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#renderpass-compatibility Render Pass Compatibility>
    -- for more information.
    GraphicsPipelineCreateInfo es -> RenderPass
renderPass :: RenderPass
  , -- | @subpass@ is the index of the subpass in the render pass where this
    -- pipeline will be used.
    GraphicsPipelineCreateInfo es -> "createInfoCount" ::: Word32
subpass :: Word32
  , -- | @basePipelineHandle@ is a pipeline to derive from.
    GraphicsPipelineCreateInfo es -> Pipeline
basePipelineHandle :: Pipeline
  , -- | @basePipelineIndex@ is an index into the @pCreateInfos@ parameter to use
    -- as a pipeline to derive from.
    GraphicsPipelineCreateInfo es -> Int32
basePipelineIndex :: Int32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (GraphicsPipelineCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (GraphicsPipelineCreateInfo es)

instance Extensible GraphicsPipelineCreateInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_GRAPHICS_PIPELINE_CREATE_INFO
  setNext :: GraphicsPipelineCreateInfo ds
-> Chain es -> GraphicsPipelineCreateInfo es
setNext x :: GraphicsPipelineCreateInfo ds
x next :: Chain es
next = GraphicsPipelineCreateInfo ds
x{$sel:next:GraphicsPipelineCreateInfo :: Chain es
next = Chain es
next}
  getNext :: GraphicsPipelineCreateInfo es -> Chain es
getNext GraphicsPipelineCreateInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends GraphicsPipelineCreateInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends GraphicsPipelineCreateInfo e => b) -> Maybe b
extends _ f :: Extends GraphicsPipelineCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineFragmentShadingRateStateCreateInfoKHR) =>
Maybe (e :~: PipelineFragmentShadingRateStateCreateInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineFragmentShadingRateStateCreateInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends GraphicsPipelineCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable PipelineCompilerControlCreateInfoAMD) =>
Maybe (e :~: PipelineCompilerControlCreateInfoAMD)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineCompilerControlCreateInfoAMD = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends GraphicsPipelineCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable PipelineCreationFeedbackCreateInfoEXT) =>
Maybe (e :~: PipelineCreationFeedbackCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineCreationFeedbackCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends GraphicsPipelineCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineRepresentativeFragmentTestStateCreateInfoNV) =>
Maybe (e :~: PipelineRepresentativeFragmentTestStateCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineRepresentativeFragmentTestStateCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends GraphicsPipelineCreateInfo e => b
f
    | Just Refl <- (Typeable e,
 Typeable PipelineDiscardRectangleStateCreateInfoEXT) =>
Maybe (e :~: PipelineDiscardRectangleStateCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineDiscardRectangleStateCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends GraphicsPipelineCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable GraphicsPipelineShaderGroupsCreateInfoNV) =>
Maybe (e :~: GraphicsPipelineShaderGroupsCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @GraphicsPipelineShaderGroupsCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends GraphicsPipelineCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss GraphicsPipelineCreateInfo es, PokeChain es) => ToCStruct (GraphicsPipelineCreateInfo es) where
  withCStruct :: GraphicsPipelineCreateInfo es
-> (Ptr (GraphicsPipelineCreateInfo es) -> IO b) -> IO b
withCStruct x :: GraphicsPipelineCreateInfo es
x f :: Ptr (GraphicsPipelineCreateInfo es) -> IO b
f = Int -> Int -> (Ptr (GraphicsPipelineCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 144 8 ((Ptr (GraphicsPipelineCreateInfo es) -> IO b) -> IO b)
-> (Ptr (GraphicsPipelineCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (GraphicsPipelineCreateInfo es)
p -> Ptr (GraphicsPipelineCreateInfo es)
-> GraphicsPipelineCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (GraphicsPipelineCreateInfo es)
p GraphicsPipelineCreateInfo es
x (Ptr (GraphicsPipelineCreateInfo es) -> IO b
f Ptr (GraphicsPipelineCreateInfo es)
p)
  pokeCStruct :: Ptr (GraphicsPipelineCreateInfo es)
-> GraphicsPipelineCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (GraphicsPipelineCreateInfo es)
p GraphicsPipelineCreateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_GRAPHICS_PIPELINE_CREATE_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineCreateFlags -> PipelineCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr PipelineCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineCreateFlags)) (PipelineCreateFlags
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ((Int -> "createInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector (SomeStruct PipelineShaderStageCreateInfo) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct PipelineShaderStageCreateInfo) -> Int)
-> Vector (SomeStruct PipelineShaderStageCreateInfo) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct PipelineShaderStageCreateInfo)
stages)) :: Word32))
    Ptr (PipelineShaderStageCreateInfo Any)
pPStages' <- ((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any)))
-> ((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(PipelineShaderStageCreateInfo _) ((Vector (SomeStruct PipelineShaderStageCreateInfo) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct PipelineShaderStageCreateInfo)
stages)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) 8
    (Int -> SomeStruct PipelineShaderStageCreateInfo -> ContT b IO ())
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct PipelineShaderStageCreateInfo
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (SomeStruct PipelineShaderStageCreateInfo)
-> SomeStruct PipelineShaderStageCreateInfo -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (PipelineShaderStageCreateInfo Any)
-> Ptr (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineShaderStageCreateInfo Any)
pPStages' Ptr (PipelineShaderStageCreateInfo Any)
-> Int -> Ptr (PipelineShaderStageCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (PipelineShaderStageCreateInfo _))) (SomeStruct PipelineShaderStageCreateInfo
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector (SomeStruct PipelineShaderStageCreateInfo)
stages)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (PipelineShaderStageCreateInfo Any))
-> Ptr (PipelineShaderStageCreateInfo Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineShaderStageCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (PipelineShaderStageCreateInfo _)))) (Ptr (PipelineShaderStageCreateInfo Any)
pPStages')
    Ptr (PipelineVertexInputStateCreateInfo '[])
pVertexInputState'' <- case (Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
vertexInputState) of
      Nothing -> Ptr (PipelineVertexInputStateCreateInfo '[])
-> ContT b IO (Ptr (PipelineVertexInputStateCreateInfo '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (PipelineVertexInputStateCreateInfo '[])
forall a. Ptr a
nullPtr
      Just j :: SomeStruct PipelineVertexInputStateCreateInfo
j -> ((Ptr (PipelineVertexInputStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineVertexInputStateCreateInfo '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (PipelineVertexInputStateCreateInfo '[])) (((Ptr (PipelineVertexInputStateCreateInfo '[]) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineVertexInputStateCreateInfo '[])))
-> ((Ptr (PipelineVertexInputStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineVertexInputStateCreateInfo '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (PipelineVertexInputStateCreateInfo '[]) -> IO b
cont -> SomeStruct PipelineVertexInputStateCreateInfo
-> (forall (es :: [*]).
    (Extendss PipelineVertexInputStateCreateInfo es, PokeChain es) =>
    Ptr (PipelineVertexInputStateCreateInfo es) -> IO b)
-> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
    (Extendss a es, PokeChain es) =>
    Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @PipelineVertexInputStateCreateInfo (SomeStruct PipelineVertexInputStateCreateInfo
j) (Ptr (PipelineVertexInputStateCreateInfo '[]) -> IO b
cont (Ptr (PipelineVertexInputStateCreateInfo '[]) -> IO b)
-> (Ptr (PipelineVertexInputStateCreateInfo es)
    -> Ptr (PipelineVertexInputStateCreateInfo '[]))
-> Ptr (PipelineVertexInputStateCreateInfo es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (PipelineVertexInputStateCreateInfo es)
-> Ptr (PipelineVertexInputStateCreateInfo '[])
forall a b. Ptr a -> Ptr b
castPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (PipelineVertexInputStateCreateInfo '[]))
-> Ptr (PipelineVertexInputStateCreateInfo '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineVertexInputStateCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr (PipelineVertexInputStateCreateInfo _)))) Ptr (PipelineVertexInputStateCreateInfo '[])
pVertexInputState''
    Ptr PipelineInputAssemblyStateCreateInfo
pInputAssemblyState'' <- case (Maybe PipelineInputAssemblyStateCreateInfo
inputAssemblyState) of
      Nothing -> Ptr PipelineInputAssemblyStateCreateInfo
-> ContT b IO (Ptr PipelineInputAssemblyStateCreateInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr PipelineInputAssemblyStateCreateInfo
forall a. Ptr a
nullPtr
      Just j :: PipelineInputAssemblyStateCreateInfo
j -> ((Ptr PipelineInputAssemblyStateCreateInfo -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineInputAssemblyStateCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PipelineInputAssemblyStateCreateInfo -> IO b) -> IO b)
 -> ContT b IO (Ptr PipelineInputAssemblyStateCreateInfo))
-> ((Ptr PipelineInputAssemblyStateCreateInfo -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineInputAssemblyStateCreateInfo)
forall a b. (a -> b) -> a -> b
$ PipelineInputAssemblyStateCreateInfo
-> (Ptr PipelineInputAssemblyStateCreateInfo -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PipelineInputAssemblyStateCreateInfo
j)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PipelineInputAssemblyStateCreateInfo)
-> Ptr PipelineInputAssemblyStateCreateInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr PipelineInputAssemblyStateCreateInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr PipelineInputAssemblyStateCreateInfo))) Ptr PipelineInputAssemblyStateCreateInfo
pInputAssemblyState''
    Ptr (PipelineTessellationStateCreateInfo '[])
pTessellationState'' <- case (Maybe (SomeStruct PipelineTessellationStateCreateInfo)
tessellationState) of
      Nothing -> Ptr (PipelineTessellationStateCreateInfo '[])
-> ContT b IO (Ptr (PipelineTessellationStateCreateInfo '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (PipelineTessellationStateCreateInfo '[])
forall a. Ptr a
nullPtr
      Just j :: SomeStruct PipelineTessellationStateCreateInfo
j -> ((Ptr (PipelineTessellationStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineTessellationStateCreateInfo '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (PipelineTessellationStateCreateInfo '[])) (((Ptr (PipelineTessellationStateCreateInfo '[]) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineTessellationStateCreateInfo '[])))
-> ((Ptr (PipelineTessellationStateCreateInfo '[]) -> IO b)
    -> IO b)
-> ContT b IO (Ptr (PipelineTessellationStateCreateInfo '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (PipelineTessellationStateCreateInfo '[]) -> IO b
cont -> SomeStruct PipelineTessellationStateCreateInfo
-> (forall (es :: [*]).
    (Extendss PipelineTessellationStateCreateInfo es, PokeChain es) =>
    Ptr (PipelineTessellationStateCreateInfo es) -> IO b)
-> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
    (Extendss a es, PokeChain es) =>
    Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @PipelineTessellationStateCreateInfo (SomeStruct PipelineTessellationStateCreateInfo
j) (Ptr (PipelineTessellationStateCreateInfo '[]) -> IO b
cont (Ptr (PipelineTessellationStateCreateInfo '[]) -> IO b)
-> (Ptr (PipelineTessellationStateCreateInfo es)
    -> Ptr (PipelineTessellationStateCreateInfo '[]))
-> Ptr (PipelineTessellationStateCreateInfo es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (PipelineTessellationStateCreateInfo es)
-> Ptr (PipelineTessellationStateCreateInfo '[])
forall a b. Ptr a -> Ptr b
castPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (PipelineTessellationStateCreateInfo '[]))
-> Ptr (PipelineTessellationStateCreateInfo '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineTessellationStateCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (PipelineTessellationStateCreateInfo _)))) Ptr (PipelineTessellationStateCreateInfo '[])
pTessellationState''
    Ptr (PipelineViewportStateCreateInfo '[])
pViewportState'' <- case (Maybe (SomeStruct PipelineViewportStateCreateInfo)
viewportState) of
      Nothing -> Ptr (PipelineViewportStateCreateInfo '[])
-> ContT b IO (Ptr (PipelineViewportStateCreateInfo '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (PipelineViewportStateCreateInfo '[])
forall a. Ptr a
nullPtr
      Just j :: SomeStruct PipelineViewportStateCreateInfo
j -> ((Ptr (PipelineViewportStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineViewportStateCreateInfo '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (PipelineViewportStateCreateInfo '[])) (((Ptr (PipelineViewportStateCreateInfo '[]) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineViewportStateCreateInfo '[])))
-> ((Ptr (PipelineViewportStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineViewportStateCreateInfo '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (PipelineViewportStateCreateInfo '[]) -> IO b
cont -> SomeStruct PipelineViewportStateCreateInfo
-> (forall (es :: [*]).
    (Extendss PipelineViewportStateCreateInfo es, PokeChain es) =>
    Ptr (PipelineViewportStateCreateInfo es) -> IO b)
-> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
    (Extendss a es, PokeChain es) =>
    Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @PipelineViewportStateCreateInfo (SomeStruct PipelineViewportStateCreateInfo
j) (Ptr (PipelineViewportStateCreateInfo '[]) -> IO b
cont (Ptr (PipelineViewportStateCreateInfo '[]) -> IO b)
-> (Ptr (PipelineViewportStateCreateInfo es)
    -> Ptr (PipelineViewportStateCreateInfo '[]))
-> Ptr (PipelineViewportStateCreateInfo es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (PipelineViewportStateCreateInfo es)
-> Ptr (PipelineViewportStateCreateInfo '[])
forall a b. Ptr a -> Ptr b
castPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (PipelineViewportStateCreateInfo '[]))
-> Ptr (PipelineViewportStateCreateInfo '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineViewportStateCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (PipelineViewportStateCreateInfo _)))) Ptr (PipelineViewportStateCreateInfo '[])
pViewportState''
    Ptr (PipelineRasterizationStateCreateInfo '[])
pRasterizationState'' <- ((Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineRasterizationStateCreateInfo '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (PipelineRasterizationStateCreateInfo '[])) (((Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineRasterizationStateCreateInfo '[])))
-> ((Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b)
    -> IO b)
-> ContT b IO (Ptr (PipelineRasterizationStateCreateInfo '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b
cont -> SomeStruct PipelineRasterizationStateCreateInfo
-> (forall (es :: [*]).
    (Extendss PipelineRasterizationStateCreateInfo es, PokeChain es) =>
    Ptr (PipelineRasterizationStateCreateInfo es) -> IO b)
-> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
    (Extendss a es, PokeChain es) =>
    Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @PipelineRasterizationStateCreateInfo (SomeStruct PipelineRasterizationStateCreateInfo
rasterizationState) (Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b
cont (Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b)
-> (Ptr (PipelineRasterizationStateCreateInfo es)
    -> Ptr (PipelineRasterizationStateCreateInfo '[]))
-> Ptr (PipelineRasterizationStateCreateInfo es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (PipelineRasterizationStateCreateInfo es)
-> Ptr (PipelineRasterizationStateCreateInfo '[])
forall a b. Ptr a -> Ptr b
castPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (PipelineRasterizationStateCreateInfo '[]))
-> Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineRasterizationStateCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr (PipelineRasterizationStateCreateInfo _)))) Ptr (PipelineRasterizationStateCreateInfo '[])
pRasterizationState''
    Ptr (PipelineMultisampleStateCreateInfo '[])
pMultisampleState'' <- case (Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
multisampleState) of
      Nothing -> Ptr (PipelineMultisampleStateCreateInfo '[])
-> ContT b IO (Ptr (PipelineMultisampleStateCreateInfo '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (PipelineMultisampleStateCreateInfo '[])
forall a. Ptr a
nullPtr
      Just j :: SomeStruct PipelineMultisampleStateCreateInfo
j -> ((Ptr (PipelineMultisampleStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineMultisampleStateCreateInfo '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (PipelineMultisampleStateCreateInfo '[])) (((Ptr (PipelineMultisampleStateCreateInfo '[]) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineMultisampleStateCreateInfo '[])))
-> ((Ptr (PipelineMultisampleStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineMultisampleStateCreateInfo '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (PipelineMultisampleStateCreateInfo '[]) -> IO b
cont -> SomeStruct PipelineMultisampleStateCreateInfo
-> (forall (es :: [*]).
    (Extendss PipelineMultisampleStateCreateInfo es, PokeChain es) =>
    Ptr (PipelineMultisampleStateCreateInfo es) -> IO b)
-> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
    (Extendss a es, PokeChain es) =>
    Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @PipelineMultisampleStateCreateInfo (SomeStruct PipelineMultisampleStateCreateInfo
j) (Ptr (PipelineMultisampleStateCreateInfo '[]) -> IO b
cont (Ptr (PipelineMultisampleStateCreateInfo '[]) -> IO b)
-> (Ptr (PipelineMultisampleStateCreateInfo es)
    -> Ptr (PipelineMultisampleStateCreateInfo '[]))
-> Ptr (PipelineMultisampleStateCreateInfo es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (PipelineMultisampleStateCreateInfo es)
-> Ptr (PipelineMultisampleStateCreateInfo '[])
forall a b. Ptr a -> Ptr b
castPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (PipelineMultisampleStateCreateInfo '[]))
-> Ptr (PipelineMultisampleStateCreateInfo '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineMultisampleStateCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr (PipelineMultisampleStateCreateInfo _)))) Ptr (PipelineMultisampleStateCreateInfo '[])
pMultisampleState''
    Ptr PipelineDepthStencilStateCreateInfo
pDepthStencilState'' <- case (Maybe PipelineDepthStencilStateCreateInfo
depthStencilState) of
      Nothing -> Ptr PipelineDepthStencilStateCreateInfo
-> ContT b IO (Ptr PipelineDepthStencilStateCreateInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr PipelineDepthStencilStateCreateInfo
forall a. Ptr a
nullPtr
      Just j :: PipelineDepthStencilStateCreateInfo
j -> ((Ptr PipelineDepthStencilStateCreateInfo -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineDepthStencilStateCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PipelineDepthStencilStateCreateInfo -> IO b) -> IO b)
 -> ContT b IO (Ptr PipelineDepthStencilStateCreateInfo))
-> ((Ptr PipelineDepthStencilStateCreateInfo -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineDepthStencilStateCreateInfo)
forall a b. (a -> b) -> a -> b
$ PipelineDepthStencilStateCreateInfo
-> (Ptr PipelineDepthStencilStateCreateInfo -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PipelineDepthStencilStateCreateInfo
j)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PipelineDepthStencilStateCreateInfo)
-> Ptr PipelineDepthStencilStateCreateInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr PipelineDepthStencilStateCreateInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr (Ptr PipelineDepthStencilStateCreateInfo))) Ptr PipelineDepthStencilStateCreateInfo
pDepthStencilState''
    Ptr (PipelineColorBlendStateCreateInfo '[])
pColorBlendState'' <- case (Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
colorBlendState) of
      Nothing -> Ptr (PipelineColorBlendStateCreateInfo '[])
-> ContT b IO (Ptr (PipelineColorBlendStateCreateInfo '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (PipelineColorBlendStateCreateInfo '[])
forall a. Ptr a
nullPtr
      Just j :: SomeStruct PipelineColorBlendStateCreateInfo
j -> ((Ptr (PipelineColorBlendStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineColorBlendStateCreateInfo '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (PipelineColorBlendStateCreateInfo '[])) (((Ptr (PipelineColorBlendStateCreateInfo '[]) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineColorBlendStateCreateInfo '[])))
-> ((Ptr (PipelineColorBlendStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineColorBlendStateCreateInfo '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (PipelineColorBlendStateCreateInfo '[]) -> IO b
cont -> SomeStruct PipelineColorBlendStateCreateInfo
-> (forall (es :: [*]).
    (Extendss PipelineColorBlendStateCreateInfo es, PokeChain es) =>
    Ptr (PipelineColorBlendStateCreateInfo es) -> IO b)
-> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
    (Extendss a es, PokeChain es) =>
    Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @PipelineColorBlendStateCreateInfo (SomeStruct PipelineColorBlendStateCreateInfo
j) (Ptr (PipelineColorBlendStateCreateInfo '[]) -> IO b
cont (Ptr (PipelineColorBlendStateCreateInfo '[]) -> IO b)
-> (Ptr (PipelineColorBlendStateCreateInfo es)
    -> Ptr (PipelineColorBlendStateCreateInfo '[]))
-> Ptr (PipelineColorBlendStateCreateInfo es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (PipelineColorBlendStateCreateInfo es)
-> Ptr (PipelineColorBlendStateCreateInfo '[])
forall a b. Ptr a -> Ptr b
castPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (PipelineColorBlendStateCreateInfo '[]))
-> Ptr (PipelineColorBlendStateCreateInfo '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineColorBlendStateCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr (Ptr (PipelineColorBlendStateCreateInfo _)))) Ptr (PipelineColorBlendStateCreateInfo '[])
pColorBlendState''
    Ptr PipelineDynamicStateCreateInfo
pDynamicState'' <- case (Maybe PipelineDynamicStateCreateInfo
dynamicState) of
      Nothing -> Ptr PipelineDynamicStateCreateInfo
-> ContT b IO (Ptr PipelineDynamicStateCreateInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr PipelineDynamicStateCreateInfo
forall a. Ptr a
nullPtr
      Just j :: PipelineDynamicStateCreateInfo
j -> ((Ptr PipelineDynamicStateCreateInfo -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineDynamicStateCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PipelineDynamicStateCreateInfo -> IO b) -> IO b)
 -> ContT b IO (Ptr PipelineDynamicStateCreateInfo))
-> ((Ptr PipelineDynamicStateCreateInfo -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineDynamicStateCreateInfo)
forall a b. (a -> b) -> a -> b
$ PipelineDynamicStateCreateInfo
-> (Ptr PipelineDynamicStateCreateInfo -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PipelineDynamicStateCreateInfo
j)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PipelineDynamicStateCreateInfo)
-> Ptr PipelineDynamicStateCreateInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr PipelineDynamicStateCreateInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr (Ptr PipelineDynamicStateCreateInfo))) Ptr PipelineDynamicStateCreateInfo
pDynamicState''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineLayout -> PipelineLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr PipelineLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr PipelineLayout)) (PipelineLayout
layout)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr RenderPass -> RenderPass -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr RenderPass
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr RenderPass)) (RenderPass
renderPass)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Word32)) ("createInfoCount" ::: Word32
subpass)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pPipelines" ::: Ptr Pipeline) -> Pipeline -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> "pPipelines" ::: Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Pipeline)) (Pipeline
basePipelineHandle)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Int32)) (Int32
basePipelineIndex)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 144
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (GraphicsPipelineCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (GraphicsPipelineCreateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_GRAPHICS_PIPELINE_CREATE_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    Ptr (PipelineShaderStageCreateInfo Any)
pPStages' <- ((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any)))
-> ((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(PipelineShaderStageCreateInfo _) ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) 8
    (Int -> SomeStruct PipelineShaderStageCreateInfo -> ContT b IO ())
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct PipelineShaderStageCreateInfo
e -> ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (SomeStruct PipelineShaderStageCreateInfo)
-> SomeStruct PipelineShaderStageCreateInfo -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (PipelineShaderStageCreateInfo Any)
-> Ptr (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineShaderStageCreateInfo Any)
pPStages' Ptr (PipelineShaderStageCreateInfo Any)
-> Int -> Ptr (PipelineShaderStageCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (PipelineShaderStageCreateInfo _))) (SomeStruct PipelineShaderStageCreateInfo
e) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())) (Vector (SomeStruct PipelineShaderStageCreateInfo)
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (PipelineShaderStageCreateInfo Any))
-> Ptr (PipelineShaderStageCreateInfo Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineShaderStageCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (PipelineShaderStageCreateInfo _)))) (Ptr (PipelineShaderStageCreateInfo Any)
pPStages')
    Ptr (PipelineRasterizationStateCreateInfo '[])
pRasterizationState'' <- ((Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineRasterizationStateCreateInfo '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (PipelineRasterizationStateCreateInfo '[])) (((Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineRasterizationStateCreateInfo '[])))
-> ((Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b)
    -> IO b)
-> ContT b IO (Ptr (PipelineRasterizationStateCreateInfo '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b
cont -> SomeStruct PipelineRasterizationStateCreateInfo
-> (forall (es :: [*]).
    (Extendss PipelineRasterizationStateCreateInfo es, PokeChain es) =>
    Ptr (PipelineRasterizationStateCreateInfo es) -> IO b)
-> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
SomeStruct a
-> (forall (es :: [*]).
    (Extendss a es, PokeChain es) =>
    Ptr (a es) -> IO b)
-> IO b
withSomeCStruct @PipelineRasterizationStateCreateInfo ((PipelineRasterizationStateCreateInfo '[]
-> SomeStruct PipelineRasterizationStateCreateInfo
forall (a :: [*] -> *) (es :: [*]).
(Extendss a es, PokeChain es, Show (Chain es)) =>
a es -> SomeStruct a
SomeStruct PipelineRasterizationStateCreateInfo '[]
forall a. Zero a => a
zero)) (Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b
cont (Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO b)
-> (Ptr (PipelineRasterizationStateCreateInfo es)
    -> Ptr (PipelineRasterizationStateCreateInfo '[]))
-> Ptr (PipelineRasterizationStateCreateInfo es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (PipelineRasterizationStateCreateInfo es)
-> Ptr (PipelineRasterizationStateCreateInfo '[])
forall a b. Ptr a -> Ptr b
castPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (PipelineRasterizationStateCreateInfo '[]))
-> Ptr (PipelineRasterizationStateCreateInfo '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineRasterizationStateCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr (PipelineRasterizationStateCreateInfo _)))) Ptr (PipelineRasterizationStateCreateInfo '[])
pRasterizationState''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PipelineLayout -> PipelineLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr PipelineLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr PipelineLayout)) (PipelineLayout
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr RenderPass -> RenderPass -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr RenderPass
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr RenderPass)) (RenderPass
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("createInfoCount" ::: Word32)
-> ("createInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Word32)) ("createInfoCount" ::: Word32
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Int32)) (Int32
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss GraphicsPipelineCreateInfo es, PeekChain es) => FromCStruct (GraphicsPipelineCreateInfo es) where
  peekCStruct :: Ptr (GraphicsPipelineCreateInfo es)
-> IO (GraphicsPipelineCreateInfo es)
peekCStruct p :: Ptr (GraphicsPipelineCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PipelineCreateFlags
flags <- Ptr PipelineCreateFlags -> IO PipelineCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineCreateFlags ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr PipelineCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineCreateFlags))
    "createInfoCount" ::: Word32
stageCount <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr (PipelineShaderStageCreateInfo Any)
pStages <- Ptr (Ptr (PipelineShaderStageCreateInfo Any))
-> IO (Ptr (PipelineShaderStageCreateInfo Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (PipelineShaderStageCreateInfo _)) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineShaderStageCreateInfo a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (PipelineShaderStageCreateInfo a))))
    Vector (SomeStruct PipelineShaderStageCreateInfo)
pStages' <- Int
-> (Int -> IO (SomeStruct PipelineShaderStageCreateInfo))
-> IO (Vector (SomeStruct PipelineShaderStageCreateInfo))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("createInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "createInfoCount" ::: Word32
stageCount) (\i :: Int
i -> Ptr (SomeStruct PipelineShaderStageCreateInfo)
-> IO (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (PipelineShaderStageCreateInfo Any)
-> Ptr (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (PipelineShaderStageCreateInfo Any)
pStages Ptr (PipelineShaderStageCreateInfo Any)
-> Int -> Ptr (PipelineShaderStageCreateInfo Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (PipelineShaderStageCreateInfo _)))))
    Ptr (PipelineVertexInputStateCreateInfo Any)
pVertexInputState <- Ptr (Ptr (PipelineVertexInputStateCreateInfo Any))
-> IO (Ptr (PipelineVertexInputStateCreateInfo Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (PipelineVertexInputStateCreateInfo _)) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineVertexInputStateCreateInfo a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr (PipelineVertexInputStateCreateInfo a))))
    Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
pVertexInputState' <- (Ptr (PipelineVertexInputStateCreateInfo Any)
 -> IO (SomeStruct PipelineVertexInputStateCreateInfo))
-> Ptr (PipelineVertexInputStateCreateInfo Any)
-> IO (Maybe (SomeStruct PipelineVertexInputStateCreateInfo))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr (PipelineVertexInputStateCreateInfo Any)
j -> Ptr (SomeStruct PipelineVertexInputStateCreateInfo)
-> IO (SomeStruct PipelineVertexInputStateCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (PipelineVertexInputStateCreateInfo Any)
-> Ptr (SomeStruct PipelineVertexInputStateCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineVertexInputStateCreateInfo Any)
j))) Ptr (PipelineVertexInputStateCreateInfo Any)
pVertexInputState
    Ptr PipelineInputAssemblyStateCreateInfo
pInputAssemblyState <- Ptr (Ptr PipelineInputAssemblyStateCreateInfo)
-> IO (Ptr PipelineInputAssemblyStateCreateInfo)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PipelineInputAssemblyStateCreateInfo) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr PipelineInputAssemblyStateCreateInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr PipelineInputAssemblyStateCreateInfo)))
    Maybe PipelineInputAssemblyStateCreateInfo
pInputAssemblyState' <- (Ptr PipelineInputAssemblyStateCreateInfo
 -> IO PipelineInputAssemblyStateCreateInfo)
-> Ptr PipelineInputAssemblyStateCreateInfo
-> IO (Maybe PipelineInputAssemblyStateCreateInfo)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr PipelineInputAssemblyStateCreateInfo
j -> Ptr PipelineInputAssemblyStateCreateInfo
-> IO PipelineInputAssemblyStateCreateInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PipelineInputAssemblyStateCreateInfo (Ptr PipelineInputAssemblyStateCreateInfo
j)) Ptr PipelineInputAssemblyStateCreateInfo
pInputAssemblyState
    Ptr (PipelineTessellationStateCreateInfo Any)
pTessellationState <- Ptr (Ptr (PipelineTessellationStateCreateInfo Any))
-> IO (Ptr (PipelineTessellationStateCreateInfo Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (PipelineTessellationStateCreateInfo _)) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineTessellationStateCreateInfo a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (PipelineTessellationStateCreateInfo a))))
    Maybe (SomeStruct PipelineTessellationStateCreateInfo)
pTessellationState' <- (Ptr (PipelineTessellationStateCreateInfo Any)
 -> IO (SomeStruct PipelineTessellationStateCreateInfo))
-> Ptr (PipelineTessellationStateCreateInfo Any)
-> IO (Maybe (SomeStruct PipelineTessellationStateCreateInfo))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr (PipelineTessellationStateCreateInfo Any)
j -> Ptr (SomeStruct PipelineTessellationStateCreateInfo)
-> IO (SomeStruct PipelineTessellationStateCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (PipelineTessellationStateCreateInfo Any)
-> Ptr (SomeStruct PipelineTessellationStateCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineTessellationStateCreateInfo Any)
j))) Ptr (PipelineTessellationStateCreateInfo Any)
pTessellationState
    Ptr (PipelineViewportStateCreateInfo Any)
pViewportState <- Ptr (Ptr (PipelineViewportStateCreateInfo Any))
-> IO (Ptr (PipelineViewportStateCreateInfo Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (PipelineViewportStateCreateInfo _)) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineViewportStateCreateInfo a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (PipelineViewportStateCreateInfo a))))
    Maybe (SomeStruct PipelineViewportStateCreateInfo)
pViewportState' <- (Ptr (PipelineViewportStateCreateInfo Any)
 -> IO (SomeStruct PipelineViewportStateCreateInfo))
-> Ptr (PipelineViewportStateCreateInfo Any)
-> IO (Maybe (SomeStruct PipelineViewportStateCreateInfo))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr (PipelineViewportStateCreateInfo Any)
j -> Ptr (SomeStruct PipelineViewportStateCreateInfo)
-> IO (SomeStruct PipelineViewportStateCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (PipelineViewportStateCreateInfo Any)
-> Ptr (SomeStruct PipelineViewportStateCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineViewportStateCreateInfo Any)
j))) Ptr (PipelineViewportStateCreateInfo Any)
pViewportState
    SomeStruct PipelineRasterizationStateCreateInfo
pRasterizationState <- Ptr (SomeStruct PipelineRasterizationStateCreateInfo)
-> IO (SomeStruct PipelineRasterizationStateCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (SomeStruct PipelineRasterizationStateCreateInfo)
 -> IO (SomeStruct PipelineRasterizationStateCreateInfo))
-> (Ptr (PipelineRasterizationStateCreateInfo Any)
    -> Ptr (SomeStruct PipelineRasterizationStateCreateInfo))
-> Ptr (PipelineRasterizationStateCreateInfo Any)
-> IO (SomeStruct PipelineRasterizationStateCreateInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (PipelineRasterizationStateCreateInfo Any)
-> Ptr (SomeStruct PipelineRasterizationStateCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineRasterizationStateCreateInfo Any)
 -> IO (SomeStruct PipelineRasterizationStateCreateInfo))
-> IO (Ptr (PipelineRasterizationStateCreateInfo Any))
-> IO (SomeStruct PipelineRasterizationStateCreateInfo)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr (PipelineRasterizationStateCreateInfo Any))
-> IO (Ptr (PipelineRasterizationStateCreateInfo Any))
forall a. Storable a => Ptr a -> IO a
peek ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineRasterizationStateCreateInfo a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr (PipelineRasterizationStateCreateInfo a))))
    Ptr (PipelineMultisampleStateCreateInfo Any)
pMultisampleState <- Ptr (Ptr (PipelineMultisampleStateCreateInfo Any))
-> IO (Ptr (PipelineMultisampleStateCreateInfo Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (PipelineMultisampleStateCreateInfo _)) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineMultisampleStateCreateInfo a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr (PipelineMultisampleStateCreateInfo a))))
    Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
pMultisampleState' <- (Ptr (PipelineMultisampleStateCreateInfo Any)
 -> IO (SomeStruct PipelineMultisampleStateCreateInfo))
-> Ptr (PipelineMultisampleStateCreateInfo Any)
-> IO (Maybe (SomeStruct PipelineMultisampleStateCreateInfo))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr (PipelineMultisampleStateCreateInfo Any)
j -> Ptr (SomeStruct PipelineMultisampleStateCreateInfo)
-> IO (SomeStruct PipelineMultisampleStateCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (PipelineMultisampleStateCreateInfo Any)
-> Ptr (SomeStruct PipelineMultisampleStateCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineMultisampleStateCreateInfo Any)
j))) Ptr (PipelineMultisampleStateCreateInfo Any)
pMultisampleState
    Ptr PipelineDepthStencilStateCreateInfo
pDepthStencilState <- Ptr (Ptr PipelineDepthStencilStateCreateInfo)
-> IO (Ptr PipelineDepthStencilStateCreateInfo)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PipelineDepthStencilStateCreateInfo) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr PipelineDepthStencilStateCreateInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr (Ptr PipelineDepthStencilStateCreateInfo)))
    Maybe PipelineDepthStencilStateCreateInfo
pDepthStencilState' <- (Ptr PipelineDepthStencilStateCreateInfo
 -> IO PipelineDepthStencilStateCreateInfo)
-> Ptr PipelineDepthStencilStateCreateInfo
-> IO (Maybe PipelineDepthStencilStateCreateInfo)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr PipelineDepthStencilStateCreateInfo
j -> Ptr PipelineDepthStencilStateCreateInfo
-> IO PipelineDepthStencilStateCreateInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PipelineDepthStencilStateCreateInfo (Ptr PipelineDepthStencilStateCreateInfo
j)) Ptr PipelineDepthStencilStateCreateInfo
pDepthStencilState
    Ptr (PipelineColorBlendStateCreateInfo Any)
pColorBlendState <- Ptr (Ptr (PipelineColorBlendStateCreateInfo Any))
-> IO (Ptr (PipelineColorBlendStateCreateInfo Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (PipelineColorBlendStateCreateInfo _)) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr (PipelineColorBlendStateCreateInfo a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr (Ptr (PipelineColorBlendStateCreateInfo a))))
    Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
pColorBlendState' <- (Ptr (PipelineColorBlendStateCreateInfo Any)
 -> IO (SomeStruct PipelineColorBlendStateCreateInfo))
-> Ptr (PipelineColorBlendStateCreateInfo Any)
-> IO (Maybe (SomeStruct PipelineColorBlendStateCreateInfo))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr (PipelineColorBlendStateCreateInfo Any)
j -> Ptr (SomeStruct PipelineColorBlendStateCreateInfo)
-> IO (SomeStruct PipelineColorBlendStateCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (PipelineColorBlendStateCreateInfo Any)
-> Ptr (SomeStruct PipelineColorBlendStateCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineColorBlendStateCreateInfo Any)
j))) Ptr (PipelineColorBlendStateCreateInfo Any)
pColorBlendState
    Ptr PipelineDynamicStateCreateInfo
pDynamicState <- Ptr (Ptr PipelineDynamicStateCreateInfo)
-> IO (Ptr PipelineDynamicStateCreateInfo)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PipelineDynamicStateCreateInfo) ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr (Ptr PipelineDynamicStateCreateInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr (Ptr PipelineDynamicStateCreateInfo)))
    Maybe PipelineDynamicStateCreateInfo
pDynamicState' <- (Ptr PipelineDynamicStateCreateInfo
 -> IO PipelineDynamicStateCreateInfo)
-> Ptr PipelineDynamicStateCreateInfo
-> IO (Maybe PipelineDynamicStateCreateInfo)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr PipelineDynamicStateCreateInfo
j -> Ptr PipelineDynamicStateCreateInfo
-> IO PipelineDynamicStateCreateInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PipelineDynamicStateCreateInfo (Ptr PipelineDynamicStateCreateInfo
j)) Ptr PipelineDynamicStateCreateInfo
pDynamicState
    PipelineLayout
layout <- Ptr PipelineLayout -> IO PipelineLayout
forall a. Storable a => Ptr a -> IO a
peek @PipelineLayout ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr PipelineLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr PipelineLayout))
    RenderPass
renderPass <- Ptr RenderPass -> IO RenderPass
forall a. Storable a => Ptr a -> IO a
peek @RenderPass ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr RenderPass
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr RenderPass))
    "createInfoCount" ::: Word32
subpass <- Ptr ("createInfoCount" ::: Word32)
-> IO ("createInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> Ptr ("createInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr Word32))
    Pipeline
basePipelineHandle <- ("pPipelines" ::: Ptr Pipeline) -> IO Pipeline
forall a. Storable a => Ptr a -> IO a
peek @Pipeline ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es)
-> Int -> "pPipelines" ::: Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr Pipeline))
    Int32
basePipelineIndex <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr (GraphicsPipelineCreateInfo es)
p Ptr (GraphicsPipelineCreateInfo es) -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr Int32))
    GraphicsPipelineCreateInfo es -> IO (GraphicsPipelineCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (GraphicsPipelineCreateInfo es
 -> IO (GraphicsPipelineCreateInfo es))
-> GraphicsPipelineCreateInfo es
-> IO (GraphicsPipelineCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineCreateFlags
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
-> Maybe PipelineInputAssemblyStateCreateInfo
-> Maybe (SomeStruct PipelineTessellationStateCreateInfo)
-> Maybe (SomeStruct PipelineViewportStateCreateInfo)
-> SomeStruct PipelineRasterizationStateCreateInfo
-> Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
-> Maybe PipelineDepthStencilStateCreateInfo
-> Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
-> Maybe PipelineDynamicStateCreateInfo
-> PipelineLayout
-> RenderPass
-> ("createInfoCount" ::: Word32)
-> Pipeline
-> Int32
-> GraphicsPipelineCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineCreateFlags
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
-> Maybe PipelineInputAssemblyStateCreateInfo
-> Maybe (SomeStruct PipelineTessellationStateCreateInfo)
-> Maybe (SomeStruct PipelineViewportStateCreateInfo)
-> SomeStruct PipelineRasterizationStateCreateInfo
-> Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
-> Maybe PipelineDepthStencilStateCreateInfo
-> Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
-> Maybe PipelineDynamicStateCreateInfo
-> PipelineLayout
-> RenderPass
-> ("createInfoCount" ::: Word32)
-> Pipeline
-> Int32
-> GraphicsPipelineCreateInfo es
GraphicsPipelineCreateInfo
             Chain es
next PipelineCreateFlags
flags Vector (SomeStruct PipelineShaderStageCreateInfo)
pStages' Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
pVertexInputState' Maybe PipelineInputAssemblyStateCreateInfo
pInputAssemblyState' Maybe (SomeStruct PipelineTessellationStateCreateInfo)
pTessellationState' Maybe (SomeStruct PipelineViewportStateCreateInfo)
pViewportState' SomeStruct PipelineRasterizationStateCreateInfo
pRasterizationState Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
pMultisampleState' Maybe PipelineDepthStencilStateCreateInfo
pDepthStencilState' Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
pColorBlendState' Maybe PipelineDynamicStateCreateInfo
pDynamicState' PipelineLayout
layout RenderPass
renderPass "createInfoCount" ::: Word32
subpass Pipeline
basePipelineHandle Int32
basePipelineIndex

instance es ~ '[] => Zero (GraphicsPipelineCreateInfo es) where
  zero :: GraphicsPipelineCreateInfo es
zero = Chain es
-> PipelineCreateFlags
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
-> Maybe PipelineInputAssemblyStateCreateInfo
-> Maybe (SomeStruct PipelineTessellationStateCreateInfo)
-> Maybe (SomeStruct PipelineViewportStateCreateInfo)
-> SomeStruct PipelineRasterizationStateCreateInfo
-> Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
-> Maybe PipelineDepthStencilStateCreateInfo
-> Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
-> Maybe PipelineDynamicStateCreateInfo
-> PipelineLayout
-> RenderPass
-> ("createInfoCount" ::: Word32)
-> Pipeline
-> Int32
-> GraphicsPipelineCreateInfo es
forall (es :: [*]).
Chain es
-> PipelineCreateFlags
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
-> Maybe PipelineInputAssemblyStateCreateInfo
-> Maybe (SomeStruct PipelineTessellationStateCreateInfo)
-> Maybe (SomeStruct PipelineViewportStateCreateInfo)
-> SomeStruct PipelineRasterizationStateCreateInfo
-> Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
-> Maybe PipelineDepthStencilStateCreateInfo
-> Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
-> Maybe PipelineDynamicStateCreateInfo
-> PipelineLayout
-> RenderPass
-> ("createInfoCount" ::: Word32)
-> Pipeline
-> Int32
-> GraphicsPipelineCreateInfo es
GraphicsPipelineCreateInfo
           ()
           PipelineCreateFlags
forall a. Zero a => a
zero
           Vector (SomeStruct PipelineShaderStageCreateInfo)
forall a. Monoid a => a
mempty
           Maybe (SomeStruct PipelineVertexInputStateCreateInfo)
forall a. Maybe a
Nothing
           Maybe PipelineInputAssemblyStateCreateInfo
forall a. Maybe a
Nothing
           Maybe (SomeStruct PipelineTessellationStateCreateInfo)
forall a. Maybe a
Nothing
           Maybe (SomeStruct PipelineViewportStateCreateInfo)
forall a. Maybe a
Nothing
           (PipelineRasterizationStateCreateInfo '[]
-> SomeStruct PipelineRasterizationStateCreateInfo
forall (a :: [*] -> *) (es :: [*]).
(Extendss a es, PokeChain es, Show (Chain es)) =>
a es -> SomeStruct a
SomeStruct PipelineRasterizationStateCreateInfo '[]
forall a. Zero a => a
zero)
           Maybe (SomeStruct PipelineMultisampleStateCreateInfo)
forall a. Maybe a
Nothing
           Maybe PipelineDepthStencilStateCreateInfo
forall a. Maybe a
Nothing
           Maybe (SomeStruct PipelineColorBlendStateCreateInfo)
forall a. Maybe a
Nothing
           Maybe PipelineDynamicStateCreateInfo
forall a. Maybe a
Nothing
           PipelineLayout
forall a. Zero a => a
zero
           RenderPass
forall a. Zero a => a
zero
           "createInfoCount" ::: Word32
forall a. Zero a => a
zero
           Pipeline
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero