{-# language CPP #-}
module Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2  ( createRenderPass2
                                                              , cmdBeginRenderPass2
                                                              , cmdUseRenderPass2
                                                              , cmdNextSubpass2
                                                              , cmdEndRenderPass2
                                                              , AttachmentDescription2(..)
                                                              , AttachmentReference2(..)
                                                              , SubpassDescription2(..)
                                                              , SubpassDependency2(..)
                                                              , RenderPassCreateInfo2(..)
                                                              , SubpassBeginInfo(..)
                                                              , SubpassEndInfo(..)
                                                              , StructureType(..)
                                                              ) where

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import 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 Foreign.Ptr (plusPtr)
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.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (peekSomeCStruct)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.CStruct.Extends (withSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Enums.AccessFlagBits (AccessFlags)
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.Enums.AttachmentDescriptionFlagBits (AttachmentDescriptionFlags)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts (AttachmentDescriptionStencilLayout)
import Vulkan.Core10.Enums.AttachmentLoadOp (AttachmentLoadOp)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts (AttachmentReferenceStencilLayout)
import Vulkan.Core10.Enums.AttachmentStoreOp (AttachmentStoreOp)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBeginRenderPass2))
import Vulkan.Dynamic (DeviceCmds(pVkCmdEndRenderPass2))
import Vulkan.Dynamic (DeviceCmds(pVkCmdNextSubpass2))
import Vulkan.Dynamic (DeviceCmds(pVkCreateRenderPass2))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.Enums.Format (Format)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_fragment_shading_rate (FragmentShadingRateAttachmentInfoKHR)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.ImageAspectFlagBits (ImageAspectFlags)
import Vulkan.Core10.Enums.ImageLayout (ImageLayout)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint)
import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlags)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Handles (RenderPass)
import Vulkan.Core10.Handles (RenderPass(..))
import Vulkan.Core10.CommandBufferBuilding (RenderPassBeginInfo)
import Vulkan.Core10.Enums.RenderPassCreateFlagBits (RenderPassCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map (RenderPassFragmentDensityMapCreateInfoEXT)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.SubpassContents (SubpassContents)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve (SubpassDescriptionDepthStencilResolve)
import Vulkan.Core10.Enums.SubpassDescriptionFlagBits (SubpassDescriptionFlags)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBPASS_BEGIN_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBPASS_DEPENDENCY_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBPASS_END_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateRenderPass2
  :: FunPtr (Ptr Device_T -> Ptr (SomeStruct RenderPassCreateInfo2) -> Ptr AllocationCallbacks -> Ptr RenderPass -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct RenderPassCreateInfo2) -> Ptr AllocationCallbacks -> Ptr RenderPass -> IO Result

-- | vkCreateRenderPass2 - Create a new render pass object
--
-- = Description
--
-- This command is functionally identical to
-- 'Vulkan.Core10.Pass.createRenderPass', but includes extensible
-- sub-structures that include @sType@ and @pNext@ parameters, allowing
-- them to be more easily extended.
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pCreateInfo@ /must/ be a valid pointer to a valid
--     'RenderPassCreateInfo2' structure
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pRenderPass@ /must/ be a valid pointer to a
--     'Vulkan.Core10.Handles.RenderPass' handle
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<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'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.RenderPass',
-- 'RenderPassCreateInfo2'
createRenderPass2 :: forall a io
                   . (Extendss RenderPassCreateInfo2 a, PokeChain a, MonadIO io)
                  => -- | @device@ is the logical device that creates the render pass.
                     Device
                  -> -- | @pCreateInfo@ is a pointer to a 'RenderPassCreateInfo2' structure
                     -- describing the parameters of the render pass.
                     (RenderPassCreateInfo2 a)
                  -> -- | @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 (RenderPass)
createRenderPass2 :: Device
-> RenderPassCreateInfo2 a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io RenderPass
createRenderPass2 device :: Device
device createInfo :: RenderPassCreateInfo2 a
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO RenderPass -> io RenderPass
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RenderPass -> io RenderPass)
-> (ContT RenderPass IO RenderPass -> IO RenderPass)
-> ContT RenderPass IO RenderPass
-> io RenderPass
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT RenderPass IO RenderPass -> IO RenderPass
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT RenderPass IO RenderPass -> io RenderPass)
-> ContT RenderPass IO RenderPass -> io RenderPass
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateRenderPass2Ptr :: FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
vkCreateRenderPass2Ptr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pRenderPass" ::: Ptr RenderPass)
      -> IO Result)
pVkCreateRenderPass2 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT RenderPass IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT RenderPass IO ())
-> IO () -> ContT RenderPass IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
vkCreateRenderPass2Ptr FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pRenderPass" ::: Ptr RenderPass)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> 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 vkCreateRenderPass2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateRenderPass2' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
vkCreateRenderPass2' = FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
mkVkCreateRenderPass2 FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pRenderPass" ::: Ptr RenderPass)
   -> IO Result)
vkCreateRenderPass2Ptr
  Ptr (RenderPassCreateInfo2 a)
pCreateInfo <- ((Ptr (RenderPassCreateInfo2 a) -> IO RenderPass) -> IO RenderPass)
-> ContT RenderPass IO (Ptr (RenderPassCreateInfo2 a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (RenderPassCreateInfo2 a) -> IO RenderPass)
  -> IO RenderPass)
 -> ContT RenderPass IO (Ptr (RenderPassCreateInfo2 a)))
-> ((Ptr (RenderPassCreateInfo2 a) -> IO RenderPass)
    -> IO RenderPass)
-> ContT RenderPass IO (Ptr (RenderPassCreateInfo2 a))
forall a b. (a -> b) -> a -> b
$ RenderPassCreateInfo2 a
-> (Ptr (RenderPassCreateInfo2 a) -> IO RenderPass)
-> IO RenderPass
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (RenderPassCreateInfo2 a
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT RenderPass 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 RenderPass)
 -> IO RenderPass)
-> ContT RenderPass 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 RenderPass)
  -> IO RenderPass)
 -> ContT RenderPass IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO RenderPass)
    -> IO RenderPass)
-> ContT RenderPass IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO RenderPass)
-> IO RenderPass
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pRenderPass" ::: Ptr RenderPass
pPRenderPass <- ((("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass)
 -> IO RenderPass)
-> ContT RenderPass IO ("pRenderPass" ::: Ptr RenderPass)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass)
  -> IO RenderPass)
 -> ContT RenderPass IO ("pRenderPass" ::: Ptr RenderPass))
-> ((("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass)
    -> IO RenderPass)
-> ContT RenderPass IO ("pRenderPass" ::: Ptr RenderPass)
forall a b. (a -> b) -> a -> b
$ IO ("pRenderPass" ::: Ptr RenderPass)
-> (("pRenderPass" ::: Ptr RenderPass) -> IO ())
-> (("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass)
-> IO RenderPass
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pRenderPass" ::: Ptr RenderPass)
forall a. Int -> IO (Ptr a)
callocBytes @RenderPass 8) ("pRenderPass" ::: Ptr RenderPass) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT RenderPass IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT RenderPass IO Result)
-> IO Result -> ContT RenderPass IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pRenderPass" ::: Ptr RenderPass)
-> IO Result
vkCreateRenderPass2' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (RenderPassCreateInfo2 a)
-> "pCreateInfo" ::: Ptr (SomeStruct RenderPassCreateInfo2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (RenderPassCreateInfo2 a)
pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pRenderPass" ::: Ptr RenderPass
pPRenderPass)
  IO () -> ContT RenderPass IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT RenderPass IO ())
-> IO () -> ContT RenderPass 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))
  RenderPass
pRenderPass <- IO RenderPass -> ContT RenderPass IO RenderPass
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO RenderPass -> ContT RenderPass IO RenderPass)
-> IO RenderPass -> ContT RenderPass IO RenderPass
forall a b. (a -> b) -> a -> b
$ ("pRenderPass" ::: Ptr RenderPass) -> IO RenderPass
forall a. Storable a => Ptr a -> IO a
peek @RenderPass "pRenderPass" ::: Ptr RenderPass
pPRenderPass
  RenderPass -> ContT RenderPass IO RenderPass
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RenderPass -> ContT RenderPass IO RenderPass)
-> RenderPass -> ContT RenderPass IO RenderPass
forall a b. (a -> b) -> a -> b
$ (RenderPass
pRenderPass)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdBeginRenderPass2
  :: FunPtr (Ptr CommandBuffer_T -> Ptr (SomeStruct RenderPassBeginInfo) -> Ptr SubpassBeginInfo -> IO ()) -> Ptr CommandBuffer_T -> Ptr (SomeStruct RenderPassBeginInfo) -> Ptr SubpassBeginInfo -> IO ()

-- | vkCmdBeginRenderPass2 - Begin a new render pass
--
-- = Description
--
-- After beginning a render pass instance, the command buffer is ready to
-- record the commands for the first subpass of that render pass.
--
-- == Valid Usage
--
-- -   Both the @framebuffer@ and @renderPass@ members of
--     @pRenderPassBegin@ /must/ have been created on the same
--     'Vulkan.Core10.Handles.Device' that @commandBuffer@ was allocated on
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_COLOR_ATTACHMENT_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   If any of the @stencilInitialLayout@ or @stencilFinalLayout@ member
--     of the
--     'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentDescriptionStencilLayout'
--     structures or the @stencilLayout@ member of the
--     'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentReferenceStencilLayout'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_SAMPLED_BIT' or
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_INPUT_ATTACHMENT_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_SRC_BIT'
--
-- -   If any of the @initialLayout@ or @finalLayout@ member of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures or the
--     @layout@ member of the 'Vulkan.Core10.Pass.AttachmentReference'
--     structures specified when creating the render pass specified in the
--     @renderPass@ member of @pRenderPassBegin@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL'
--     then the corresponding attachment image view of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@ /must/
--     have been created with a @usage@ value including
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.IMAGE_USAGE_TRANSFER_DST_BIT'
--
-- -   If any of the @initialLayout@ members of the
--     'Vulkan.Core10.Pass.AttachmentDescription' structures specified when
--     creating the render pass specified in the @renderPass@ member of
--     @pRenderPassBegin@ is not
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED', then each
--     such @initialLayout@ /must/ be equal to the current layout of the
--     corresponding attachment image subresource of the framebuffer
--     specified in the @framebuffer@ member of @pRenderPassBegin@
--
-- -   The @srcStageMask@ and @dstStageMask@ members of any element of the
--     @pDependencies@ member of 'Vulkan.Core10.Pass.RenderPassCreateInfo'
--     used to create @renderPass@ /must/ be supported by the capabilities
--     of the queue family identified by the @queueFamilyIndex@ member of
--     the 'Vulkan.Core10.CommandPool.CommandPoolCreateInfo' used to create
--     the command pool which @commandBuffer@ was allocated from
--
-- -   For any attachment in @framebuffer@ that is used by @renderPass@ and
--     is bound to memory locations that are also bound to another
--     attachment used by @renderPass@, and if at least one of those uses
--     causes either attachment to be written to, both attachments /must/
--     have had the
--     'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT'
--     set
--
-- -   Each element of the @pAttachments@ of @framebuffer@ that is
--     referenced by any element of the @pInputAttachments@ of any element
--     of @pSubpasses@ of @renderPass@ /must/ have
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features image view format features>
--     contain at least
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--     or
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   Each element of the @pAttachments@ of @framebuffer@ that is
--     referenced by any element of the @pColorAttachments@ of any element
--     of @pSubpasses@ of @renderPass@ /must/ have
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features image view format features>
--     contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--
-- -   Each element of the @pAttachments@ of @framebuffer@ that is
--     referenced by any element of the @pResolveAttachments@ of any
--     element of @pSubpasses@ of @renderPass@ /must/ have
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features image view format features>
--     contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--
-- -   Each element of the @pAttachments@ of @framebuffer@ that is
--     referenced by any element of the @pDepthStencilAttachment@ of any
--     element of @pSubpasses@ of @renderPass@ /must/ have
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features image view format features>
--     contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pRenderPassBegin@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo' structure
--
-- -   @pSubpassBeginInfo@ /must/ be a valid pointer to a valid
--     'SubpassBeginInfo' structure
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @commandBuffer@ /must/ be a primary
--     'Vulkan.Core10.Handles.CommandBuffer'
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Graphics                                                                                                              | Graphics                                                                                                                            |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo',
-- 'SubpassBeginInfo'
cmdBeginRenderPass2 :: forall a io
                     . (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io)
                    => -- | @commandBuffer@ is the command buffer in which to record the command.
                       CommandBuffer
                    -> -- | @pRenderPassBegin@ is a pointer to a
                       -- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo' structure
                       -- specifying the render pass to begin an instance of, and the framebuffer
                       -- the instance uses.
                       (RenderPassBeginInfo a)
                    -> -- | @pSubpassBeginInfo@ is a pointer to a 'SubpassBeginInfo' structure
                       -- containing information about the subpass which is about to begin
                       -- rendering.
                       SubpassBeginInfo
                    -> io ()
cmdBeginRenderPass2 :: CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> io ()
cmdBeginRenderPass2 commandBuffer :: CommandBuffer
commandBuffer renderPassBegin :: RenderPassBeginInfo a
renderPassBegin subpassBeginInfo :: SubpassBeginInfo
subpassBeginInfo = 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 vkCmdBeginRenderPass2Ptr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> IO ())
vkCmdBeginRenderPass2Ptr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
      -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
      -> IO ())
pVkCmdBeginRenderPass2 (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> IO ())
vkCmdBeginRenderPass2Ptr FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
      -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> 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 vkCmdBeginRenderPass2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBeginRenderPass2' :: Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ()
vkCmdBeginRenderPass2' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ()
mkVkCmdBeginRenderPass2 FunPtr
  (Ptr CommandBuffer_T
   -> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> IO ())
vkCmdBeginRenderPass2Ptr
  Ptr (RenderPassBeginInfo a)
pRenderPassBegin <- ((Ptr (RenderPassBeginInfo a) -> IO ()) -> IO ())
-> ContT () IO (Ptr (RenderPassBeginInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (RenderPassBeginInfo a) -> IO ()) -> IO ())
 -> ContT () IO (Ptr (RenderPassBeginInfo a)))
-> ((Ptr (RenderPassBeginInfo a) -> IO ()) -> IO ())
-> ContT () IO (Ptr (RenderPassBeginInfo a))
forall a b. (a -> b) -> a -> b
$ RenderPassBeginInfo a
-> (Ptr (RenderPassBeginInfo a) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (RenderPassBeginInfo a
renderPassBegin)
  "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
pSubpassBeginInfo <- ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
 -> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
  -> IO ())
 -> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo))
-> ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
    -> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
forall a b. (a -> b) -> a -> b
$ SubpassBeginInfo
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SubpassBeginInfo
subpassBeginInfo)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo))
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO ()
vkCmdBeginRenderPass2' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Ptr (RenderPassBeginInfo a)
-> "pRenderPassBegin" ::: Ptr (SomeStruct RenderPassBeginInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (RenderPassBeginInfo a)
pRenderPassBegin) "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
pSubpassBeginInfo
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()

-- | This function will call the supplied action between calls to
-- 'cmdBeginRenderPass2' and 'cmdEndRenderPass2'
--
-- Note that 'cmdEndRenderPass2' is *not* called if an exception is thrown
-- by the inner action.
cmdUseRenderPass2 :: forall a io r . (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> SubpassEndInfo -> io r -> io r
cmdUseRenderPass2 :: CommandBuffer
-> RenderPassBeginInfo a
-> SubpassBeginInfo
-> SubpassEndInfo
-> io r
-> io r
cmdUseRenderPass2 commandBuffer :: CommandBuffer
commandBuffer pRenderPassBegin :: RenderPassBeginInfo a
pRenderPassBegin pSubpassBeginInfo :: SubpassBeginInfo
pSubpassBeginInfo pSubpassEndInfo :: SubpassEndInfo
pSubpassEndInfo a :: io r
a =
  (CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> io ()
forall (a :: [*]) (io :: * -> *).
(Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) =>
CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> io ()
cmdBeginRenderPass2 CommandBuffer
commandBuffer RenderPassBeginInfo a
pRenderPassBegin SubpassBeginInfo
pSubpassBeginInfo) io () -> io r -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> io r
a io r -> io () -> io r
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* (CommandBuffer -> SubpassEndInfo -> io ()
forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> SubpassEndInfo -> io ()
cmdEndRenderPass2 CommandBuffer
commandBuffer SubpassEndInfo
pSubpassEndInfo)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdNextSubpass2
  :: FunPtr (Ptr CommandBuffer_T -> Ptr SubpassBeginInfo -> Ptr SubpassEndInfo -> IO ()) -> Ptr CommandBuffer_T -> Ptr SubpassBeginInfo -> Ptr SubpassEndInfo -> IO ()

-- | vkCmdNextSubpass2 - Transition to the next subpass of a render pass
--
-- = Description
--
-- 'cmdNextSubpass2' is semantically identical to
-- 'Vulkan.Core10.CommandBufferBuilding.cmdNextSubpass', except that it is
-- extensible, and that @contents@ is provided as part of an extensible
-- structure instead of as a flat parameter.
--
-- == Valid Usage
--
-- -   The current subpass index /must/ be less than the number of
--     subpasses in the render pass minus one
--
-- -   This command /must/ not be recorded when transform feedback is
--     active
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pSubpassBeginInfo@ /must/ be a valid pointer to a valid
--     'SubpassBeginInfo' structure
--
-- -   @pSubpassEndInfo@ /must/ be a valid pointer to a valid
--     'SubpassEndInfo' structure
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   This command /must/ only be called inside of a render pass instance
--
-- -   @commandBuffer@ /must/ be a primary
--     'Vulkan.Core10.Handles.CommandBuffer'
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Inside                                                                                                                 | Graphics                                                                                                              | Graphics                                                                                                                            |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'SubpassBeginInfo',
-- 'SubpassEndInfo'
cmdNextSubpass2 :: forall io
                 . (MonadIO io)
                => -- | @commandBuffer@ is the command buffer in which to record the command.
                   CommandBuffer
                -> -- | @pSubpassBeginInfo@ is a pointer to a 'SubpassBeginInfo' structure
                   -- containing information about the subpass which is about to begin
                   -- rendering.
                   SubpassBeginInfo
                -> -- | @pSubpassEndInfo@ is a pointer to a 'SubpassEndInfo' structure
                   -- containing information about how the previous subpass will be ended.
                   SubpassEndInfo
                -> io ()
cmdNextSubpass2 :: CommandBuffer -> SubpassBeginInfo -> SubpassEndInfo -> io ()
cmdNextSubpass2 commandBuffer :: CommandBuffer
commandBuffer subpassBeginInfo :: SubpassBeginInfo
subpassBeginInfo subpassEndInfo :: SubpassEndInfo
subpassEndInfo = 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 vkCmdNextSubpass2Ptr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
   -> IO ())
vkCmdNextSubpass2Ptr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
      -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
      -> IO ())
pVkCmdNextSubpass2 (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
   -> IO ())
vkCmdNextSubpass2Ptr FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
      -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
   -> 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 vkCmdNextSubpass2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdNextSubpass2' :: Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ()
vkCmdNextSubpass2' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ()
mkVkCmdNextSubpass2 FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
   -> IO ())
vkCmdNextSubpass2Ptr
  "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
pSubpassBeginInfo <- ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
 -> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
  -> IO ())
 -> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo))
-> ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
    -> IO ())
-> ContT () IO ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
forall a b. (a -> b) -> a -> b
$ SubpassBeginInfo
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SubpassBeginInfo
subpassBeginInfo)
  "pSubpassEndInfo" ::: Ptr SubpassEndInfo
pSubpassEndInfo <- ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
 -> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo))
-> ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
forall a b. (a -> b) -> a -> b
$ SubpassEndInfo
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SubpassEndInfo
subpassEndInfo)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ()
vkCmdNextSubpass2' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
pSubpassBeginInfo "pSubpassEndInfo" ::: Ptr SubpassEndInfo
pSubpassEndInfo
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdEndRenderPass2
  :: FunPtr (Ptr CommandBuffer_T -> Ptr SubpassEndInfo -> IO ()) -> Ptr CommandBuffer_T -> Ptr SubpassEndInfo -> IO ()

-- | vkCmdEndRenderPass2 - End the current render pass
--
-- = Description
--
-- 'cmdEndRenderPass2' is semantically identical to
-- 'Vulkan.Core10.CommandBufferBuilding.cmdEndRenderPass', except that it
-- is extensible.
--
-- == Valid Usage
--
-- -   The current subpass index /must/ be equal to the number of subpasses
--     in the render pass minus one
--
-- -   This command /must/ not be recorded when transform feedback is
--     active
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pSubpassEndInfo@ /must/ be a valid pointer to a valid
--     'SubpassEndInfo' structure
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics operations
--
-- -   This command /must/ only be called inside of a render pass instance
--
-- -   @commandBuffer@ /must/ be a primary
--     'Vulkan.Core10.Handles.CommandBuffer'
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Inside                                                                                                                 | Graphics                                                                                                              | Graphics                                                                                                                            |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'SubpassEndInfo'
cmdEndRenderPass2 :: forall io
                   . (MonadIO io)
                  => -- | @commandBuffer@ is the command buffer in which to end the current render
                     -- pass instance.
                     CommandBuffer
                  -> -- | @pSubpassEndInfo@ is a pointer to a 'SubpassEndInfo' structure
                     -- containing information about how the previous subpass will be ended.
                     SubpassEndInfo
                  -> io ()
cmdEndRenderPass2 :: CommandBuffer -> SubpassEndInfo -> io ()
cmdEndRenderPass2 commandBuffer :: CommandBuffer
commandBuffer subpassEndInfo :: SubpassEndInfo
subpassEndInfo = 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 vkCmdEndRenderPass2Ptr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
vkCmdEndRenderPass2Ptr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
pVkCmdEndRenderPass2 (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
vkCmdEndRenderPass2Ptr FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> 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 vkCmdEndRenderPass2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdEndRenderPass2' :: Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()
vkCmdEndRenderPass2' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
-> Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> IO ()
mkVkCmdEndRenderPass2 FunPtr
  (Ptr CommandBuffer_T
   -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ())
vkCmdEndRenderPass2Ptr
  "pSubpassEndInfo" ::: Ptr SubpassEndInfo
pSubpassEndInfo <- ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
 -> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo))
-> ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ())
-> ContT () IO ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
forall a b. (a -> b) -> a -> b
$ SubpassEndInfo
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SubpassEndInfo
subpassEndInfo)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CommandBuffer_T
-> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO ()
vkCmdEndRenderPass2' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pSubpassEndInfo" ::: Ptr SubpassEndInfo
pSubpassEndInfo
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkAttachmentDescription2 - Structure specifying an attachment
-- description
--
-- = Description
--
-- Parameters defined by this structure with the same name as those in
-- 'Vulkan.Core10.Pass.AttachmentDescription' have the identical effect to
-- those parameters.
--
-- If the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts>
-- feature is enabled, and @format@ is a depth\/stencil format,
-- @initialLayout@ and @finalLayout@ /can/ be set to a layout that only
-- specifies the layout of the depth aspect.
--
-- If @format@ is a depth\/stencil format, and @initialLayout@ only
-- specifies the initial layout of the depth aspect of the attachment, the
-- initial layout of the stencil aspect is specified by the
-- @stencilInitialLayout@ member of a
-- 'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentDescriptionStencilLayout'
-- structure included in the @pNext@ chain. Otherwise, @initialLayout@
-- describes the initial layout for all relevant image aspects.
--
-- If @format@ is a depth\/stencil format, and @finalLayout@ only specifies
-- the final layout of the depth aspect of the attachment, the final layout
-- of the stencil aspect is specified by the @stencilFinalLayout@ member of
-- a
-- 'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentDescriptionStencilLayout'
-- structure included in the @pNext@ chain. Otherwise, @finalLayout@
-- describes the final layout for all relevant image aspects.
--
-- == Valid Usage
--
-- -   @finalLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED' or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PREINITIALIZED'
--
-- -   If @format@ is a color format, @initialLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL'
--
-- -   If @format@ is a depth\/stencil format, @initialLayout@ /must/ not
--     be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL'
--
-- -   If @format@ is a color format, @finalLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL'
--
-- -   If @format@ is a depth\/stencil format, @finalLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts>
--     feature is not enabled, @initialLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts>
--     feature is not enabled, @finalLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--
-- -   If @format@ is a color format, @initialLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--
-- -   If @format@ is a color format, @finalLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--
-- -   If @format@ is a depth\/stencil format which includes both depth and
--     stencil aspects, and @initialLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     the @pNext@ chain /must/ include a
--     'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentDescriptionStencilLayout'
--     structure
--
-- -   If @format@ is a depth\/stencil format which includes both depth and
--     stencil aspects, and @finalLayout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     the @pNext@ chain /must/ include a
--     'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentDescriptionStencilLayout'
--     structure
--
-- -   If @format@ is a depth\/stencil format which includes only the depth
--     aspect, @initialLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--
-- -   If @format@ is a depth\/stencil format which includes only the depth
--     aspect, @finalLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--
-- -   If @format@ is a depth\/stencil format which includes only the
--     stencil aspect, @initialLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL'
--
-- -   If @format@ is a depth\/stencil format which includes only the
--     stencil aspect, @finalLayout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_2'
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.AttachmentDescriptionFlagBits'
--     values
--
-- -   @format@ /must/ be a valid 'Vulkan.Core10.Enums.Format.Format' value
--
-- -   @samples@ /must/ be a valid
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' value
--
-- -   @loadOp@ /must/ be a valid
--     'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp' value
--
-- -   @storeOp@ /must/ be a valid
--     'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp' value
--
-- -   @stencilLoadOp@ /must/ be a valid
--     'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp' value
--
-- -   @stencilStoreOp@ /must/ be a valid
--     'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp' value
--
-- -   @initialLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- -   @finalLayout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.AttachmentDescriptionFlags',
-- 'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp',
-- 'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp',
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout', 'RenderPassCreateInfo2',
-- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AttachmentDescription2 (es :: [Type]) = AttachmentDescription2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    AttachmentDescription2 es -> Chain es
next :: Chain es
  , -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.AttachmentDescriptionFlagBits'
    -- specifying additional properties of the attachment.
    AttachmentDescription2 es -> AttachmentDescriptionFlags
flags :: AttachmentDescriptionFlags
  , -- | @format@ is a 'Vulkan.Core10.Enums.Format.Format' value specifying the
    -- format of the image that will be used for the attachment.
    AttachmentDescription2 es -> Format
format :: Format
  , -- | @samples@ is the number of samples of the image as defined in
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits'.
    AttachmentDescription2 es -> SampleCountFlagBits
samples :: SampleCountFlagBits
  , -- | @loadOp@ is a 'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp'
    -- value specifying how the contents of color and depth components of the
    -- attachment are treated at the beginning of the subpass where it is first
    -- used.
    AttachmentDescription2 es -> AttachmentLoadOp
loadOp :: AttachmentLoadOp
  , -- | @storeOp@ is a 'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp'
    -- value specifying how the contents of color and depth components of the
    -- attachment are treated at the end of the subpass where it is last used.
    AttachmentDescription2 es -> AttachmentStoreOp
storeOp :: AttachmentStoreOp
  , -- | @stencilLoadOp@ is a
    -- 'Vulkan.Core10.Enums.AttachmentLoadOp.AttachmentLoadOp' value specifying
    -- how the contents of stencil components of the attachment are treated at
    -- the beginning of the subpass where it is first used.
    AttachmentDescription2 es -> AttachmentLoadOp
stencilLoadOp :: AttachmentLoadOp
  , -- | @stencilStoreOp@ is a
    -- 'Vulkan.Core10.Enums.AttachmentStoreOp.AttachmentStoreOp' value
    -- specifying how the contents of stencil components of the attachment are
    -- treated at the end of the last subpass where it is used.
    AttachmentDescription2 es -> AttachmentStoreOp
stencilStoreOp :: AttachmentStoreOp
  , -- | @initialLayout@ is the layout the attachment image subresource will be
    -- in when a render pass instance begins.
    AttachmentDescription2 es -> ImageLayout
initialLayout :: ImageLayout
  , -- | @finalLayout@ is the layout the attachment image subresource will be
    -- transitioned to when a render pass instance ends.
    AttachmentDescription2 es -> ImageLayout
finalLayout :: ImageLayout
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AttachmentDescription2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (AttachmentDescription2 es)

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

instance (Extendss AttachmentDescription2 es, PokeChain es) => ToCStruct (AttachmentDescription2 es) where
  withCStruct :: AttachmentDescription2 es
-> (Ptr (AttachmentDescription2 es) -> IO b) -> IO b
withCStruct x :: AttachmentDescription2 es
x f :: Ptr (AttachmentDescription2 es) -> IO b
f = Int -> Int -> (Ptr (AttachmentDescription2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((Ptr (AttachmentDescription2 es) -> IO b) -> IO b)
-> (Ptr (AttachmentDescription2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (AttachmentDescription2 es)
p -> Ptr (AttachmentDescription2 es)
-> AttachmentDescription2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (AttachmentDescription2 es)
p AttachmentDescription2 es
x (Ptr (AttachmentDescription2 es) -> IO b
f Ptr (AttachmentDescription2 es)
p)
  pokeCStruct :: Ptr (AttachmentDescription2 es)
-> AttachmentDescription2 es -> IO b -> IO b
pokeCStruct p :: Ptr (AttachmentDescription2 es)
p AttachmentDescription2{..} 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 (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_2)
    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 (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 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 AttachmentDescriptionFlags
-> AttachmentDescriptionFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es)
-> Int -> Ptr AttachmentDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AttachmentDescriptionFlags)) (AttachmentDescriptionFlags
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 Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Format)) (Format
format)
    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 (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
samples)
    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 AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
loadOp)
    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 AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
storeOp)
    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 AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
stencilLoadOp)
    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 AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
stencilStoreOp)
    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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr ImageLayout)) (ImageLayout
initialLayout)
    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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr ImageLayout)) (ImageLayout
finalLayout)
    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 (AttachmentDescription2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (AttachmentDescription2 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 (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_2)
    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 (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 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 Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Format)) (Format
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 SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: 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 AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
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 AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
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 AttachmentLoadOp -> AttachmentLoadOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AttachmentLoadOp)) (AttachmentLoadOp
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 AttachmentStoreOp -> AttachmentStoreOp -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr AttachmentStoreOp)) (AttachmentStoreOp
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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr ImageLayout)) (ImageLayout
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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr ImageLayout)) (ImageLayout
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 AttachmentDescription2 es, PeekChain es) => FromCStruct (AttachmentDescription2 es) where
  peekCStruct :: Ptr (AttachmentDescription2 es) -> IO (AttachmentDescription2 es)
peekCStruct p :: Ptr (AttachmentDescription2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 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)
    AttachmentDescriptionFlags
flags <- Ptr AttachmentDescriptionFlags -> IO AttachmentDescriptionFlags
forall a. Storable a => Ptr a -> IO a
peek @AttachmentDescriptionFlags ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es)
-> Int -> Ptr AttachmentDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AttachmentDescriptionFlags))
    Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Format))
    SampleCountFlagBits
samples <- Ptr SampleCountFlagBits -> IO SampleCountFlagBits
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlagBits ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlagBits))
    AttachmentLoadOp
loadOp <- Ptr AttachmentLoadOp -> IO AttachmentLoadOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentLoadOp ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr AttachmentLoadOp))
    AttachmentStoreOp
storeOp <- Ptr AttachmentStoreOp -> IO AttachmentStoreOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentStoreOp ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AttachmentStoreOp))
    AttachmentLoadOp
stencilLoadOp <- Ptr AttachmentLoadOp -> IO AttachmentLoadOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentLoadOp ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentLoadOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AttachmentLoadOp))
    AttachmentStoreOp
stencilStoreOp <- Ptr AttachmentStoreOp -> IO AttachmentStoreOp
forall a. Storable a => Ptr a -> IO a
peek @AttachmentStoreOp ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr AttachmentStoreOp
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr AttachmentStoreOp))
    ImageLayout
initialLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr ImageLayout))
    ImageLayout
finalLayout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (AttachmentDescription2 es)
p Ptr (AttachmentDescription2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr ImageLayout))
    AttachmentDescription2 es -> IO (AttachmentDescription2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AttachmentDescription2 es -> IO (AttachmentDescription2 es))
-> AttachmentDescription2 es -> IO (AttachmentDescription2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription2 es
forall (es :: [*]).
Chain es
-> AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription2 es
AttachmentDescription2
             Chain es
next AttachmentDescriptionFlags
flags Format
format SampleCountFlagBits
samples AttachmentLoadOp
loadOp AttachmentStoreOp
storeOp AttachmentLoadOp
stencilLoadOp AttachmentStoreOp
stencilStoreOp ImageLayout
initialLayout ImageLayout
finalLayout

instance es ~ '[] => Zero (AttachmentDescription2 es) where
  zero :: AttachmentDescription2 es
zero = Chain es
-> AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription2 es
forall (es :: [*]).
Chain es
-> AttachmentDescriptionFlags
-> Format
-> SampleCountFlagBits
-> AttachmentLoadOp
-> AttachmentStoreOp
-> AttachmentLoadOp
-> AttachmentStoreOp
-> ImageLayout
-> ImageLayout
-> AttachmentDescription2 es
AttachmentDescription2
           ()
           AttachmentDescriptionFlags
forall a. Zero a => a
zero
           Format
forall a. Zero a => a
zero
           SampleCountFlagBits
forall a. Zero a => a
zero
           AttachmentLoadOp
forall a. Zero a => a
zero
           AttachmentStoreOp
forall a. Zero a => a
zero
           AttachmentLoadOp
forall a. Zero a => a
zero
           AttachmentStoreOp
forall a. Zero a => a
zero
           ImageLayout
forall a. Zero a => a
zero
           ImageLayout
forall a. Zero a => a
zero


-- | VkAttachmentReference2 - Structure specifying an attachment reference
--
-- = Description
--
-- Parameters defined by this structure with the same name as those in
-- 'Vulkan.Core10.Pass.AttachmentReference' have the identical effect to
-- those parameters.
--
-- @aspectMask@ is ignored when this structure is used to describe anything
-- other than an input attachment reference.
--
-- If the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts>
-- feature is enabled, and @attachment@ has a depth\/stencil format,
-- @layout@ /can/ be set to a layout that only specifies the layout of the
-- depth aspect.
--
-- If @layout@ only specifies the layout of the depth aspect of the
-- attachment, the layout of the stencil aspect is specified by the
-- @stencilLayout@ member of a
-- 'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentReferenceStencilLayout'
-- structure included in the @pNext@ chain. Otherwise, @layout@ describes
-- the layout for all relevant image aspects.
--
-- == Valid Usage
--
-- -   If @attachment@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', @layout@ /must/ not
--     be 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_UNDEFINED',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PREINITIALIZED', or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_PRESENT_SRC_KHR'
--
-- -   If @attachment@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', and @aspectMask@
--     does not include
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--     or 'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT',
--     @layout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL'
--
-- -   If @attachment@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', and @aspectMask@
--     does not include
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT',
--     @layout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-separateDepthStencilLayouts separateDepthStencilLayouts>
--     feature is not enabled, and @attachment@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', @layout@ /must/ not
--     be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL',
--
-- -   If @attachment@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', and @aspectMask@
--     includes
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_COLOR_BIT',
--     @layout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL',
--
-- -   If @attachment@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', and @aspectMask@
--     includes both
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT' and
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT',
--     and @layout@ is
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL'
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL',
--     the @pNext@ chain /must/ include a
--     'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.AttachmentReferenceStencilLayout'
--     structure
--
-- -   If @attachment@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', and @aspectMask@
--     includes only
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_DEPTH_BIT'
--     then @layout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL'
--
-- -   If @attachment@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', and @aspectMask@
--     includes only
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_STENCIL_BIT'
--     then @layout@ /must/ not be
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2'
--
-- -   @layout@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FragmentShadingRateAttachmentInfoKHR',
-- 'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlags',
-- 'Vulkan.Core10.Enums.ImageLayout.ImageLayout',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'SubpassDescription2',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve.SubpassDescriptionDepthStencilResolve'
data AttachmentReference2 (es :: [Type]) = AttachmentReference2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    AttachmentReference2 es -> Chain es
next :: Chain es
  , -- | @attachment@ is either an integer value identifying an attachment at the
    -- corresponding index in
    -- 'Vulkan.Core10.Pass.RenderPassCreateInfo'::@pAttachments@, or
    -- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' to signify that this
    -- attachment is not used.
    AttachmentReference2 es -> Word32
attachment :: Word32
  , -- | @layout@ is a 'Vulkan.Core10.Enums.ImageLayout.ImageLayout' value
    -- specifying the layout the attachment uses during the subpass.
    AttachmentReference2 es -> ImageLayout
layout :: ImageLayout
  , -- | @aspectMask@ is a mask of which aspect(s) /can/ be accessed within the
    -- specified subpass as an input attachment.
    AttachmentReference2 es -> ImageAspectFlags
aspectMask :: ImageAspectFlags
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AttachmentReference2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (AttachmentReference2 es)

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

instance (Extendss AttachmentReference2 es, PokeChain es) => ToCStruct (AttachmentReference2 es) where
  withCStruct :: AttachmentReference2 es
-> (Ptr (AttachmentReference2 es) -> IO b) -> IO b
withCStruct x :: AttachmentReference2 es
x f :: Ptr (AttachmentReference2 es) -> IO b
f = Int -> Int -> (Ptr (AttachmentReference2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr (AttachmentReference2 es) -> IO b) -> IO b)
-> (Ptr (AttachmentReference2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (AttachmentReference2 es)
p -> Ptr (AttachmentReference2 es)
-> AttachmentReference2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (AttachmentReference2 es)
p AttachmentReference2 es
x (Ptr (AttachmentReference2 es) -> IO b
f Ptr (AttachmentReference2 es)
p)
  pokeCStruct :: Ptr (AttachmentReference2 es)
-> AttachmentReference2 es -> IO b -> IO b
pokeCStruct p :: Ptr (AttachmentReference2 es)
p AttachmentReference2{..} 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 (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2)
    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 (AttachmentReference2 es)
p Ptr (AttachmentReference2 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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
attachment)
    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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageLayout)) (ImageLayout
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 ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageAspectFlags)) (ImageAspectFlags
aspectMask)
    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 (AttachmentReference2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (AttachmentReference2 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 (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2)
    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 (AttachmentReference2 es)
p Ptr (AttachmentReference2 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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (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 ImageLayout -> ImageLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageLayout)) (ImageLayout
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 ImageAspectFlags -> ImageAspectFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageAspectFlags)) (ImageAspectFlags
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 AttachmentReference2 es, PeekChain es) => FromCStruct (AttachmentReference2 es) where
  peekCStruct :: Ptr (AttachmentReference2 es) -> IO (AttachmentReference2 es)
peekCStruct p :: Ptr (AttachmentReference2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 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)
    Word32
attachment <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    ImageLayout
layout <- Ptr ImageLayout -> IO ImageLayout
forall a. Storable a => Ptr a -> IO a
peek @ImageLayout ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageLayout))
    ImageAspectFlags
aspectMask <- Ptr ImageAspectFlags -> IO ImageAspectFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageAspectFlags ((Ptr (AttachmentReference2 es)
p Ptr (AttachmentReference2 es) -> Int -> Ptr ImageAspectFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageAspectFlags))
    AttachmentReference2 es -> IO (AttachmentReference2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AttachmentReference2 es -> IO (AttachmentReference2 es))
-> AttachmentReference2 es -> IO (AttachmentReference2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> Word32
-> ImageLayout
-> ImageAspectFlags
-> AttachmentReference2 es
forall (es :: [*]).
Chain es
-> Word32
-> ImageLayout
-> ImageAspectFlags
-> AttachmentReference2 es
AttachmentReference2
             Chain es
next Word32
attachment ImageLayout
layout ImageAspectFlags
aspectMask

instance es ~ '[] => Zero (AttachmentReference2 es) where
  zero :: AttachmentReference2 es
zero = Chain es
-> Word32
-> ImageLayout
-> ImageAspectFlags
-> AttachmentReference2 es
forall (es :: [*]).
Chain es
-> Word32
-> ImageLayout
-> ImageAspectFlags
-> AttachmentReference2 es
AttachmentReference2
           ()
           Word32
forall a. Zero a => a
zero
           ImageLayout
forall a. Zero a => a
zero
           ImageAspectFlags
forall a. Zero a => a
zero


-- | VkSubpassDescription2 - Structure specifying a subpass description
--
-- = Description
--
-- Parameters defined by this structure with the same name as those in
-- 'Vulkan.Core10.Pass.SubpassDescription' have the identical effect to
-- those parameters.
--
-- @viewMask@ has the same effect for the described subpass as
-- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo'::@pViewMasks@
-- has on each corresponding subpass.
--
-- If an instance of
-- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FragmentShadingRateAttachmentInfoKHR'
-- is included in the @pNext@ chain, @pFragmentShadingRateAttachment@ is
-- not @NULL@, and its @attachment@ member is not
-- 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', the identified
-- attachment defines a fragment shading rate attachment for that subpass.
--
-- == Valid Usage
--
-- -   @pipelineBindPoint@ /must/ be
--     'Vulkan.Core10.Enums.PipelineBindPoint.PIPELINE_BIND_POINT_GRAPHICS'
--
-- -   @colorAttachmentCount@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxColorAttachments@
--
-- -   If the first use of an attachment in this render pass is as an input
--     attachment, and the attachment is not also used as a color or
--     depth\/stencil attachment in the same subpass, then @loadOp@ /must/
--     not be
--     'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR'
--
-- -   If @pResolveAttachments@ is not @NULL@, for each resolve attachment
--     that does not have the value
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', the corresponding
--     color attachment /must/ not have the value
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED'
--
-- -   If @pResolveAttachments@ is not @NULL@, for each resolve attachment
--     that is not 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', the
--     corresponding color attachment /must/ not have a sample count of
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   If @pResolveAttachments@ is not @NULL@, each resolve attachment that
--     is not 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have a
--     sample count of
--     'Vulkan.Core10.Enums.SampleCountFlagBits.SAMPLE_COUNT_1_BIT'
--
-- -   Any given element of @pResolveAttachments@ /must/ have the same
--     'Vulkan.Core10.Enums.Format.Format' as its corresponding color
--     attachment
--
-- -   All attachments in @pColorAttachments@ that are not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have the same
--     sample count
--
-- -   All attachments in @pInputAttachments@ that are not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have image
--     formats whose
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#potential-format-features potential format features>
--     contain at least
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--     or
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   All attachments in @pColorAttachments@ that are not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have image
--     formats whose
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#potential-format-features potential format features>
--     contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--
-- -   All attachments in @pResolveAttachments@ that are not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have image
--     formats whose
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#potential-format-features potential format features>
--     contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT'
--
-- -   If @pDepthStencilAttachment@ is not @NULL@ and the attachment is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' then it /must/ have a
--     image format whose
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#potential-format-features potential format features>
--     contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT'
--
-- -   If the @VK_AMD_mixed_attachment_samples@ extension is enabled, all
--     attachments in @pColorAttachments@ that are not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' /must/ have a sample
--     count that is smaller than or equal to the sample count of
--     @pDepthStencilAttachment@ if it is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED'
--
-- -   If neither the @VK_AMD_mixed_attachment_samples@ nor the
--     @VK_NV_framebuffer_mixed_samples@ extensions are enabled, and if
--     @pDepthStencilAttachment@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED' and any attachments
--     in @pColorAttachments@ are not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', they /must/ have the
--     same sample count
--
-- -   The @attachment@ member of any element of @pPreserveAttachments@
--     /must/ not be 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED'
--
-- -   Any given element of @pPreserveAttachments@ /must/ not also be an
--     element of any other member of the subpass description
--
-- -   If any attachment is used by more than one
--     'Vulkan.Core10.Pass.AttachmentReference' member, then each use
--     /must/ use the same @layout@
--
-- -   Attachments /must/ follow the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#attachment-type-imagelayout image layout requirements>
--     based on the type of attachment it is being used as
--
-- -   If @flags@ includes
--     'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SUBPASS_DESCRIPTION_PER_VIEW_POSITION_X_ONLY_BIT_NVX',
--     it /must/ also include
--     'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SUBPASS_DESCRIPTION_PER_VIEW_ATTRIBUTES_BIT_NVX'
--
-- -   If the @attachment@ member of any element of @pInputAttachments@ is
--     not 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', then the
--     @aspectMask@ member /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.ImageAspectFlagBits'
--
-- -   If the @attachment@ member of any element of @pInputAttachments@ is
--     not 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', then the
--     @aspectMask@ member /must/ not be @0@
--
-- -   If the @attachment@ member of any element of @pInputAttachments@ is
--     not 'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', then the
--     @aspectMask@ member /must/ not include
--     'Vulkan.Core10.Enums.ImageAspectFlagBits.IMAGE_ASPECT_METADATA_BIT'
--
-- -   An attachment /must/ not be used in both @pDepthStencilAttachment@
--     and @pColorAttachments@
--
-- -   If the @pFragmentShadingRateAttachment@ member of a
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FragmentShadingRateAttachmentInfoKHR'
--     structure included in the @pNext@ chain is not @NULL@, and its
--     @attachment@ member is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', that attachment
--     /must/ not be used as any other attachment in this subpass
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2'
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SubpassDescriptionFlagBits'
--     values
--
-- -   @pipelineBindPoint@ /must/ be a valid
--     'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value
--
-- -   If @inputAttachmentCount@ is not @0@, @pInputAttachments@ /must/ be
--     a valid pointer to an array of @inputAttachmentCount@ valid
--     'AttachmentReference2' structures
--
-- -   If @colorAttachmentCount@ is not @0@, @pColorAttachments@ /must/ be
--     a valid pointer to an array of @colorAttachmentCount@ valid
--     'AttachmentReference2' structures
--
-- -   If @colorAttachmentCount@ is not @0@, and @pResolveAttachments@ is
--     not @NULL@, @pResolveAttachments@ /must/ be a valid pointer to an
--     array of @colorAttachmentCount@ valid 'AttachmentReference2'
--     structures
--
-- -   If @pDepthStencilAttachment@ is not @NULL@,
--     @pDepthStencilAttachment@ /must/ be a valid pointer to a valid
--     'AttachmentReference2' structure
--
-- -   If @preserveAttachmentCount@ is not @0@, @pPreserveAttachments@
--     /must/ be a valid pointer to an array of @preserveAttachmentCount@
--     @uint32_t@ values
--
-- = See Also
--
-- 'AttachmentReference2',
-- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint',
-- 'RenderPassCreateInfo2',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SubpassDescriptionFlags'
data SubpassDescription2 (es :: [Type]) = SubpassDescription2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    SubpassDescription2 es -> Chain es
next :: Chain es
  , -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.SubpassDescriptionFlagBits.SubpassDescriptionFlagBits'
    -- specifying usage of the subpass.
    SubpassDescription2 es -> SubpassDescriptionFlags
flags :: SubpassDescriptionFlags
  , -- | @pipelineBindPoint@ is a
    -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value
    -- specifying the pipeline type supported for this subpass.
    SubpassDescription2 es -> PipelineBindPoint
pipelineBindPoint :: PipelineBindPoint
  , -- | @viewMask@ is a bitfield of view indices describing which views
    -- rendering is broadcast to in this subpass, when multiview is enabled.
    SubpassDescription2 es -> Word32
viewMask :: Word32
  , -- | @pInputAttachments@ is a pointer to an array of 'AttachmentReference2'
    -- structures defining the input attachments for this subpass and their
    -- layouts.
    SubpassDescription2 es -> Vector (SomeStruct AttachmentReference2)
inputAttachments :: Vector (SomeStruct AttachmentReference2)
  , -- | @pColorAttachments@ is a pointer to an array of 'AttachmentReference2'
    -- structures defining the color attachments for this subpass and their
    -- layouts.
    SubpassDescription2 es -> Vector (SomeStruct AttachmentReference2)
colorAttachments :: Vector (SomeStruct AttachmentReference2)
  , -- | @pResolveAttachments@ is an optional array of @colorAttachmentCount@
    -- 'AttachmentReference2' structures defining the resolve attachments for
    -- this subpass and their layouts.
    SubpassDescription2 es -> Vector (SomeStruct AttachmentReference2)
resolveAttachments :: Vector (SomeStruct AttachmentReference2)
  , -- | @pDepthStencilAttachment@ is a pointer to a 'AttachmentReference2'
    -- structure specifying the depth\/stencil attachment for this subpass and
    -- its layout.
    SubpassDescription2 es -> Maybe (SomeStruct AttachmentReference2)
depthStencilAttachment :: Maybe (SomeStruct AttachmentReference2)
  , -- | @pPreserveAttachments@ is a pointer to an array of
    -- @preserveAttachmentCount@ render pass attachment indices identifying
    -- attachments that are not used by this subpass, but whose contents /must/
    -- be preserved throughout the subpass.
    SubpassDescription2 es -> Vector Word32
preserveAttachments :: Vector Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SubpassDescription2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (SubpassDescription2 es)

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

instance (Extendss SubpassDescription2 es, PokeChain es) => ToCStruct (SubpassDescription2 es) where
  withCStruct :: SubpassDescription2 es
-> (Ptr (SubpassDescription2 es) -> IO b) -> IO b
withCStruct x :: SubpassDescription2 es
x f :: Ptr (SubpassDescription2 es) -> IO b
f = Int -> Int -> (Ptr (SubpassDescription2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 88 8 ((Ptr (SubpassDescription2 es) -> IO b) -> IO b)
-> (Ptr (SubpassDescription2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (SubpassDescription2 es)
p -> Ptr (SubpassDescription2 es)
-> SubpassDescription2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (SubpassDescription2 es)
p SubpassDescription2 es
x (Ptr (SubpassDescription2 es) -> IO b
f Ptr (SubpassDescription2 es)
p)
  pokeCStruct :: Ptr (SubpassDescription2 es)
-> SubpassDescription2 es -> IO b -> IO b
pokeCStruct p :: Ptr (SubpassDescription2 es)
p SubpassDescription2{..} 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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2)
    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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 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 SubpassDescriptionFlags -> SubpassDescriptionFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr SubpassDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SubpassDescriptionFlags)) (SubpassDescriptionFlags
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 PipelineBindPoint -> PipelineBindPoint -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr PipelineBindPoint)) (PipelineBindPoint
pipelineBindPoint)
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
viewMask)
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2) -> Int)
-> Vector (SomeStruct AttachmentReference2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct AttachmentReference2)
inputAttachments)) :: Word32))
    Ptr (AttachmentReference2 Any)
pPInputAttachments' <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) ((Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2)
inputAttachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32) 8
    (Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 AttachmentReference2)
-> SomeStruct AttachmentReference2 -> 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 (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPInputAttachments' Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 AttachmentReference2)
inputAttachments)
    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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr (AttachmentReference2 _)))) (Ptr (AttachmentReference2 Any)
pPInputAttachments')
    let pColorAttachmentsLength :: Int
pColorAttachmentsLength = Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2) -> Int)
-> Vector (SomeStruct AttachmentReference2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct AttachmentReference2)
colorAttachments)
    let pResolveAttachmentsLength :: Int
pResolveAttachmentsLength = Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2) -> Int)
-> Vector (SomeStruct AttachmentReference2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct AttachmentReference2)
resolveAttachments)
    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 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pResolveAttachmentsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pColorAttachmentsLength Bool -> Bool -> Bool
|| Int
pResolveAttachmentsLength 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 "" "pResolveAttachments and pColorAttachments must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pColorAttachmentsLength :: Word32))
    Ptr (AttachmentReference2 Any)
pPColorAttachments' <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) ((Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2)
colorAttachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32) 8
    (Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 AttachmentReference2)
-> SomeStruct AttachmentReference2 -> 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 (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPColorAttachments' Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 AttachmentReference2)
colorAttachments)
    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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (AttachmentReference2 _)))) (Ptr (AttachmentReference2 Any)
pPColorAttachments')
    Ptr (AttachmentReference2 Any)
pResolveAttachments'' <- if Vector (SomeStruct AttachmentReference2) -> Bool
forall a. Vector a -> Bool
Data.Vector.null (Vector (SomeStruct AttachmentReference2)
resolveAttachments)
      then Ptr (AttachmentReference2 Any)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (AttachmentReference2 Any)
forall a. Ptr a
nullPtr
      else do
        Ptr (AttachmentReference2 Any)
pPResolveAttachments <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) (((Vector (SomeStruct AttachmentReference2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentReference2)
resolveAttachments))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 32) 8
        (Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 AttachmentReference2)
-> SomeStruct AttachmentReference2 -> 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 (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPResolveAttachments Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 AttachmentReference2)
resolveAttachments))
        Ptr (AttachmentReference2 Any)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr (AttachmentReference2 Any)
 -> ContT b IO (Ptr (AttachmentReference2 Any)))
-> Ptr (AttachmentReference2 Any)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Ptr (AttachmentReference2 Any)
pPResolveAttachments
    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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (AttachmentReference2 _)))) Ptr (AttachmentReference2 Any)
pResolveAttachments''
    Ptr (AttachmentReference2 '[])
pDepthStencilAttachment'' <- case (Maybe (SomeStruct AttachmentReference2)
depthStencilAttachment) of
      Nothing -> Ptr (AttachmentReference2 '[])
-> ContT b IO (Ptr (AttachmentReference2 '[]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr (AttachmentReference2 '[])
forall a. Ptr a
nullPtr
      Just j :: SomeStruct AttachmentReference2
j -> ((Ptr (AttachmentReference2 '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 '[]))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT @_ @_ @(Ptr (AttachmentReference2 '[])) (((Ptr (AttachmentReference2 '[]) -> IO b) -> IO b)
 -> ContT b IO (Ptr (AttachmentReference2 '[])))
-> ((Ptr (AttachmentReference2 '[]) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 '[]))
forall a b. (a -> b) -> a -> b
$ \cont :: Ptr (AttachmentReference2 '[]) -> IO b
cont -> SomeStruct AttachmentReference2
-> (forall (es :: [*]).
    (Extendss AttachmentReference2 es, PokeChain es) =>
    Ptr (AttachmentReference2 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 @AttachmentReference2 (SomeStruct AttachmentReference2
j) (Ptr (AttachmentReference2 '[]) -> IO b
cont (Ptr (AttachmentReference2 '[]) -> IO b)
-> (Ptr (AttachmentReference2 es)
    -> Ptr (AttachmentReference2 '[]))
-> Ptr (AttachmentReference2 es)
-> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (AttachmentReference2 es) -> Ptr (AttachmentReference2 '[])
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 (AttachmentReference2 '[]))
-> Ptr (AttachmentReference2 '[]) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr (AttachmentReference2 _)))) Ptr (AttachmentReference2 '[])
pDepthStencilAttachment''
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
preserveAttachments)) :: Word32))
    Ptr Word32
pPPreserveAttachments' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32
preserveAttachments)) 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 -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPPreserveAttachments' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
preserveAttachments)
    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 Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr (Ptr Word32))) (Ptr Word32
pPPreserveAttachments')
    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 = 88
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (SubpassDescription2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (SubpassDescription2 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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2)
    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 (SubpassDescription2 es)
p Ptr (SubpassDescription2 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 PipelineBindPoint -> PipelineBindPoint -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr PipelineBindPoint)) (PipelineBindPoint
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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr (AttachmentReference2 Any)
pPInputAttachments' <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) ((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) 8
    (Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 AttachmentReference2)
-> SomeStruct AttachmentReference2 -> 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 (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPInputAttachments' Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 AttachmentReference2)
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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr (AttachmentReference2 _)))) (Ptr (AttachmentReference2 Any)
pPInputAttachments')
    Ptr (AttachmentReference2 Any)
pPColorAttachments' <- ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (AttachmentReference2 Any)))
-> ((Ptr (AttachmentReference2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentReference2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentReference2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentReference2 _) ((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) 8
    (Int -> SomeStruct AttachmentReference2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentReference2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentReference2
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 AttachmentReference2)
-> SomeStruct AttachmentReference2 -> 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 (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
pPColorAttachments' Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _))) (SomeStruct AttachmentReference2
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 AttachmentReference2)
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 (AttachmentReference2 Any))
-> Ptr (AttachmentReference2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (AttachmentReference2 _)))) (Ptr (AttachmentReference2 Any)
pPColorAttachments')
    Ptr Word32
pPPreserveAttachments' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((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 -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPPreserveAttachments' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
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 Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr (Ptr Word32))) (Ptr Word32
pPPreserveAttachments')
    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 SubpassDescription2 es, PeekChain es) => FromCStruct (SubpassDescription2 es) where
  peekCStruct :: Ptr (SubpassDescription2 es) -> IO (SubpassDescription2 es)
peekCStruct p :: Ptr (SubpassDescription2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 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)
    SubpassDescriptionFlags
flags <- Ptr SubpassDescriptionFlags -> IO SubpassDescriptionFlags
forall a. Storable a => Ptr a -> IO a
peek @SubpassDescriptionFlags ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr SubpassDescriptionFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SubpassDescriptionFlags))
    PipelineBindPoint
pipelineBindPoint <- Ptr PipelineBindPoint -> IO PipelineBindPoint
forall a. Storable a => Ptr a -> IO a
peek @PipelineBindPoint ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr PipelineBindPoint
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr PipelineBindPoint))
    Word32
viewMask <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    Word32
inputAttachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
    Ptr (AttachmentReference2 Any)
pInputAttachments <- Ptr (Ptr (AttachmentReference2 Any))
-> IO (Ptr (AttachmentReference2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentReference2 _)) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr (AttachmentReference2 a))))
    Vector (SomeStruct AttachmentReference2)
pInputAttachments' <- Int
-> (Int -> IO (SomeStruct AttachmentReference2))
-> IO (Vector (SomeStruct AttachmentReference2))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
inputAttachmentCount) (\i :: Int
i -> Ptr (SomeStruct AttachmentReference2)
-> IO (SomeStruct AttachmentReference2)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (AttachmentReference2 Any)
pInputAttachments Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _)))))
    Word32
colorAttachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32))
    Ptr (AttachmentReference2 Any)
pColorAttachments <- Ptr (Ptr (AttachmentReference2 Any))
-> IO (Ptr (AttachmentReference2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentReference2 _)) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (AttachmentReference2 a))))
    Vector (SomeStruct AttachmentReference2)
pColorAttachments' <- Int
-> (Int -> IO (SomeStruct AttachmentReference2))
-> IO (Vector (SomeStruct AttachmentReference2))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
colorAttachmentCount) (\i :: Int
i -> Ptr (SomeStruct AttachmentReference2)
-> IO (SomeStruct AttachmentReference2)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (AttachmentReference2 Any)
pColorAttachments Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _)))))
    Ptr (AttachmentReference2 Any)
pResolveAttachments <- Ptr (Ptr (AttachmentReference2 Any))
-> IO (Ptr (AttachmentReference2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentReference2 _)) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (AttachmentReference2 a))))
    let pResolveAttachmentsLength :: Int
pResolveAttachmentsLength = if Ptr (AttachmentReference2 Any)
pResolveAttachments Ptr (AttachmentReference2 Any)
-> Ptr (AttachmentReference2 Any) -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr (AttachmentReference2 Any)
forall a. Ptr a
nullPtr then 0 else (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
colorAttachmentCount)
    Vector (SomeStruct AttachmentReference2)
pResolveAttachments' <- Int
-> (Int -> IO (SomeStruct AttachmentReference2))
-> IO (Vector (SomeStruct AttachmentReference2))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM Int
pResolveAttachmentsLength (\i :: Int
i -> Ptr (SomeStruct AttachmentReference2)
-> IO (SomeStruct AttachmentReference2)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (AttachmentReference2 Any)
pResolveAttachments Ptr (AttachmentReference2 Any)
-> Int -> Ptr (AttachmentReference2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (32 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentReference2 _)))))
    Ptr (AttachmentReference2 Any)
pDepthStencilAttachment <- Ptr (Ptr (AttachmentReference2 Any))
-> IO (Ptr (AttachmentReference2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentReference2 _)) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es)
-> Int -> Ptr (Ptr (AttachmentReference2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr (AttachmentReference2 a))))
    Maybe (SomeStruct AttachmentReference2)
pDepthStencilAttachment' <- (Ptr (AttachmentReference2 Any)
 -> IO (SomeStruct AttachmentReference2))
-> Ptr (AttachmentReference2 Any)
-> IO (Maybe (SomeStruct AttachmentReference2))
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr (AttachmentReference2 Any)
j -> Ptr (SomeStruct AttachmentReference2)
-> IO (SomeStruct AttachmentReference2)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentReference2 Any)
-> Ptr (SomeStruct AttachmentReference2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentReference2 Any)
j))) Ptr (AttachmentReference2 Any)
pDepthStencilAttachment
    Word32
preserveAttachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr Word32))
    Ptr Word32
pPreserveAttachments <- Ptr (Ptr Word32) -> IO (Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr (SubpassDescription2 es)
p Ptr (SubpassDescription2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr (Ptr Word32)))
    Vector Word32
pPreserveAttachments' <- Int -> (Int -> IO Word32) -> IO (Vector Word32)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
preserveAttachmentCount) (\i :: Int
i -> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pPreserveAttachments Ptr Word32 -> Int -> Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    SubpassDescription2 es -> IO (SubpassDescription2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassDescription2 es -> IO (SubpassDescription2 es))
-> SubpassDescription2 es -> IO (SubpassDescription2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> SubpassDescriptionFlags
-> PipelineBindPoint
-> Word32
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Maybe (SomeStruct AttachmentReference2)
-> Vector Word32
-> SubpassDescription2 es
forall (es :: [*]).
Chain es
-> SubpassDescriptionFlags
-> PipelineBindPoint
-> Word32
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Maybe (SomeStruct AttachmentReference2)
-> Vector Word32
-> SubpassDescription2 es
SubpassDescription2
             Chain es
next SubpassDescriptionFlags
flags PipelineBindPoint
pipelineBindPoint Word32
viewMask Vector (SomeStruct AttachmentReference2)
pInputAttachments' Vector (SomeStruct AttachmentReference2)
pColorAttachments' Vector (SomeStruct AttachmentReference2)
pResolveAttachments' Maybe (SomeStruct AttachmentReference2)
pDepthStencilAttachment' Vector Word32
pPreserveAttachments'

instance es ~ '[] => Zero (SubpassDescription2 es) where
  zero :: SubpassDescription2 es
zero = Chain es
-> SubpassDescriptionFlags
-> PipelineBindPoint
-> Word32
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Maybe (SomeStruct AttachmentReference2)
-> Vector Word32
-> SubpassDescription2 es
forall (es :: [*]).
Chain es
-> SubpassDescriptionFlags
-> PipelineBindPoint
-> Word32
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Vector (SomeStruct AttachmentReference2)
-> Maybe (SomeStruct AttachmentReference2)
-> Vector Word32
-> SubpassDescription2 es
SubpassDescription2
           ()
           SubpassDescriptionFlags
forall a. Zero a => a
zero
           PipelineBindPoint
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Vector (SomeStruct AttachmentReference2)
forall a. Monoid a => a
mempty
           Vector (SomeStruct AttachmentReference2)
forall a. Monoid a => a
mempty
           Vector (SomeStruct AttachmentReference2)
forall a. Monoid a => a
mempty
           Maybe (SomeStruct AttachmentReference2)
forall a. Maybe a
Nothing
           Vector Word32
forall a. Monoid a => a
mempty


-- | VkSubpassDependency2 - Structure specifying a subpass dependency
--
-- = Description
--
-- Parameters defined by this structure with the same name as those in
-- 'Vulkan.Core10.Pass.SubpassDependency' have the identical effect to
-- those parameters.
--
-- @viewOffset@ has the same effect for the described subpass dependency as
-- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo'::@pViewOffsets@
-- has on each corresponding subpass dependency.
--
-- == 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, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   @srcSubpass@ /must/ be less than or equal to @dstSubpass@, unless
--     one of them is 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', to
--     avoid cyclic dependencies and ensure a valid execution order
--
-- -   @srcSubpass@ and @dstSubpass@ /must/ not both be equal to
--     'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL'
--
-- -   If @srcSubpass@ is equal to @dstSubpass@ and not all of the stages
--     in @srcStageMask@ and @dstStageMask@ are
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stages>,
--     the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-order logically latest>
--     pipeline stage in @srcStageMask@ /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-order logically earlier>
--     than or equal to the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-order logically earliest>
--     pipeline stage in @dstStageMask@
--
-- -   Any access flag included in @srcAccessMask@ /must/ be supported by
--     one of the pipeline stages in @srcStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   Any access flag included in @dstAccessMask@ /must/ be supported by
--     one of the pipeline stages in @dstStageMask@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types-supported table of supported access types>
--
-- -   If @dependencyFlags@ includes
--     'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT',
--     @srcSubpass@ /must/ not be equal to
--     'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL'
--
-- -   If @dependencyFlags@ includes
--     'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT',
--     @dstSubpass@ /must/ not be equal to
--     'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL'
--
-- -   If @srcSubpass@ equals @dstSubpass@, and @srcStageMask@ and
--     @dstStageMask@ both include a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-framebuffer-regions framebuffer-space stage>,
--     then @dependencyFlags@ /must/ include
--     'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_BY_REGION_BIT'
--
-- -   If @viewOffset@ is not equal to @0@, @srcSubpass@ /must/ not be
--     equal to @dstSubpass@
--
-- -   If @dependencyFlags@ does not include
--     'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT',
--     @viewOffset@ /must/ be @0@
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shaders>
--     feature is not enabled, @srcStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shaders>
--     feature is not enabled, @dstStageMask@ /must/ not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SUBPASS_DEPENDENCY_2'
--
-- -   @srcStageMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     values
--
-- -   @srcStageMask@ /must/ not be @0@
--
-- -   @dstStageMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     values
--
-- -   @dstStageMask@ /must/ not be @0@
--
-- -   @srcAccessMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' values
--
-- -   @dstAccessMask@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' values
--
-- -   @dependencyFlags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlagBits' values
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlags',
-- 'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlags',
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlags',
-- 'RenderPassCreateInfo2',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data SubpassDependency2 = SubpassDependency2
  { -- | @srcSubpass@ is the subpass index of the first subpass in the
    -- dependency, or 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL'.
    SubpassDependency2 -> Word32
srcSubpass :: Word32
  , -- | @dstSubpass@ is the subpass index of the second subpass in the
    -- dependency, or 'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL'.
    SubpassDependency2 -> Word32
dstSubpass :: Word32
  , -- | @srcStageMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
    -- specifying the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks source stage mask>.
    SubpassDependency2 -> PipelineStageFlags
srcStageMask :: PipelineStageFlags
  , -- | @dstStageMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
    -- specifying the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-masks destination stage mask>
    SubpassDependency2 -> PipelineStageFlags
dstStageMask :: PipelineStageFlags
  , -- | @srcAccessMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks source access mask>.
    SubpassDependency2 -> AccessFlags
srcAccessMask :: AccessFlags
  , -- | @dstAccessMask@ is a bitmask of
    -- 'Vulkan.Core10.Enums.AccessFlagBits.AccessFlagBits' specifying a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-masks destination access mask>.
    SubpassDependency2 -> AccessFlags
dstAccessMask :: AccessFlags
  , -- | @dependencyFlags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.DependencyFlagBits.DependencyFlagBits'.
    SubpassDependency2 -> DependencyFlags
dependencyFlags :: DependencyFlags
  , -- | @viewOffset@ controls which views in the source subpass the views in the
    -- destination subpass depend on.
    SubpassDependency2 -> Int32
viewOffset :: Int32
  }
  deriving (Typeable, SubpassDependency2 -> SubpassDependency2 -> Bool
(SubpassDependency2 -> SubpassDependency2 -> Bool)
-> (SubpassDependency2 -> SubpassDependency2 -> Bool)
-> Eq SubpassDependency2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubpassDependency2 -> SubpassDependency2 -> Bool
$c/= :: SubpassDependency2 -> SubpassDependency2 -> Bool
== :: SubpassDependency2 -> SubpassDependency2 -> Bool
$c== :: SubpassDependency2 -> SubpassDependency2 -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SubpassDependency2)
#endif
deriving instance Show SubpassDependency2

instance ToCStruct SubpassDependency2 where
  withCStruct :: SubpassDependency2 -> (Ptr SubpassDependency2 -> IO b) -> IO b
withCStruct x :: SubpassDependency2
x f :: Ptr SubpassDependency2 -> IO b
f = Int -> Int -> (Ptr SubpassDependency2 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> (Ptr SubpassDependency2 -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SubpassDependency2
p -> Ptr SubpassDependency2 -> SubpassDependency2 -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SubpassDependency2
p SubpassDependency2
x (Ptr SubpassDependency2 -> IO b
f Ptr SubpassDependency2
p)
  pokeCStruct :: Ptr SubpassDependency2 -> SubpassDependency2 -> IO b -> IO b
pokeCStruct p :: Ptr SubpassDependency2
p SubpassDependency2{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DEPENDENCY_2)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
srcSubpass)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
dstSubpass)
    Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr PipelineStageFlags)) (PipelineStageFlags
srcStageMask)
    Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr PipelineStageFlags)) (PipelineStageFlags
dstStageMask)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AccessFlags)) (AccessFlags
srcAccessMask)
    Ptr AccessFlags -> AccessFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AccessFlags)) (AccessFlags
dstAccessMask)
    Ptr DependencyFlags -> DependencyFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr DependencyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DependencyFlags)) (DependencyFlags
dependencyFlags)
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Int32)) (Int32
viewOffset)
    IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr SubpassDependency2 -> IO b -> IO b
pokeZeroCStruct p :: Ptr SubpassDependency2
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_DEPENDENCY_2)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr PipelineStageFlags)) (PipelineStageFlags
forall a. Zero a => a
zero)
    Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr PipelineStageFlags)) (PipelineStageFlags
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct SubpassDependency2 where
  peekCStruct :: Ptr SubpassDependency2 -> IO SubpassDependency2
peekCStruct p :: Ptr SubpassDependency2
p = do
    Word32
srcSubpass <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Word32
dstSubpass <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    PipelineStageFlags
srcStageMask <- Ptr PipelineStageFlags -> IO PipelineStageFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineStageFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr PipelineStageFlags))
    PipelineStageFlags
dstStageMask <- Ptr PipelineStageFlags -> IO PipelineStageFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineStageFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr PipelineStageFlags))
    AccessFlags
srcAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AccessFlags))
    AccessFlags
dstAccessMask <- Ptr AccessFlags -> IO AccessFlags
forall a. Storable a => Ptr a -> IO a
peek @AccessFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr AccessFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr AccessFlags))
    DependencyFlags
dependencyFlags <- Ptr DependencyFlags -> IO DependencyFlags
forall a. Storable a => Ptr a -> IO a
peek @DependencyFlags ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr DependencyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DependencyFlags))
    Int32
viewOffset <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr SubpassDependency2
p Ptr SubpassDependency2 -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Int32))
    SubpassDependency2 -> IO SubpassDependency2
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassDependency2 -> IO SubpassDependency2)
-> SubpassDependency2 -> IO SubpassDependency2
forall a b. (a -> b) -> a -> b
$ Word32
-> Word32
-> PipelineStageFlags
-> PipelineStageFlags
-> AccessFlags
-> AccessFlags
-> DependencyFlags
-> Int32
-> SubpassDependency2
SubpassDependency2
             Word32
srcSubpass Word32
dstSubpass PipelineStageFlags
srcStageMask PipelineStageFlags
dstStageMask AccessFlags
srcAccessMask AccessFlags
dstAccessMask DependencyFlags
dependencyFlags Int32
viewOffset

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

instance Zero SubpassDependency2 where
  zero :: SubpassDependency2
zero = Word32
-> Word32
-> PipelineStageFlags
-> PipelineStageFlags
-> AccessFlags
-> AccessFlags
-> DependencyFlags
-> Int32
-> SubpassDependency2
SubpassDependency2
           Word32
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           PipelineStageFlags
forall a. Zero a => a
zero
           PipelineStageFlags
forall a. Zero a => a
zero
           AccessFlags
forall a. Zero a => a
zero
           AccessFlags
forall a. Zero a => a
zero
           DependencyFlags
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero


-- | VkRenderPassCreateInfo2 - Structure specifying parameters of a newly
-- created render pass
--
-- = Description
--
-- Parameters defined by this structure with the same name as those in
-- 'Vulkan.Core10.Pass.RenderPassCreateInfo' have the identical effect to
-- those parameters; the child structures are variants of those used in
-- 'Vulkan.Core10.Pass.RenderPassCreateInfo' which add @sType@ and @pNext@
-- parameters, allowing them to be extended.
--
-- If the 'SubpassDescription2'::@viewMask@ member of any element of
-- @pSubpasses@ is not zero, /multiview/ functionality is considered to be
-- enabled for this render pass.
--
-- @correlatedViewMaskCount@ and @pCorrelatedViewMasks@ have the same
-- effect as
-- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo'::@correlationMaskCount@
-- and
-- 'Vulkan.Core11.Promoted_From_VK_KHR_multiview.RenderPassMultiviewCreateInfo'::@pCorrelationMasks@,
-- respectively.
--
-- == Valid Usage
--
-- -   If any two subpasses operate on attachments with overlapping ranges
--     of the same 'Vulkan.Core10.Handles.DeviceMemory' object, and at
--     least one subpass writes to that area of
--     'Vulkan.Core10.Handles.DeviceMemory', a subpass dependency /must/ be
--     included (either directly or via some intermediate subpasses)
--     between them
--
-- -   If the @attachment@ member of any element of @pInputAttachments@,
--     @pColorAttachments@, @pResolveAttachments@ or
--     @pDepthStencilAttachment@, or the attachment indexed by any element
--     of @pPreserveAttachments@ in any given element of @pSubpasses@ is
--     bound to a range of a 'Vulkan.Core10.Handles.DeviceMemory' object
--     that overlaps with any other attachment in any subpass (including
--     the same subpass), the 'AttachmentDescription2' structures
--     describing them /must/ include
--     'Vulkan.Core10.Enums.AttachmentDescriptionFlagBits.ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT'
--     in @flags@
--
-- -   If the @attachment@ member of any element of @pInputAttachments@,
--     @pColorAttachments@, @pResolveAttachments@ or
--     @pDepthStencilAttachment@, or any element of @pPreserveAttachments@
--     in any given element of @pSubpasses@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', it /must/ be less
--     than @attachmentCount@
--
-- -   For any member of @pAttachments@ with a @loadOp@ equal to
--     'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR', the
--     first use of that attachment /must/ not specify a @layout@ equal to
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL'
--
-- -   For any member of @pAttachments@ with a @stencilLoadOp@ equal to
--     'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR', the
--     first use of that attachment /must/ not specify a @layout@ equal to
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL',
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL',
--     or
--     'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL'
--
-- -   For any element of @pDependencies@, if the @srcSubpass@ is not
--     'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', all stage flags
--     included in the @srcStageMask@ member of that dependency /must/ be a
--     pipeline stage supported by the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types pipeline>
--     identified by the @pipelineBindPoint@ member of the source subpass
--
-- -   For any element of @pDependencies@, if the @dstSubpass@ is not
--     'Vulkan.Core10.APIConstants.SUBPASS_EXTERNAL', all stage flags
--     included in the @dstStageMask@ member of that dependency /must/ be a
--     pipeline stage supported by the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types pipeline>
--     identified by the @pipelineBindPoint@ member of the destination
--     subpass
--
-- -   The set of bits included in any element of @pCorrelatedViewMasks@
--     /must/ not overlap with the set of bits included in any other
--     element of @pCorrelatedViewMasks@
--
-- -   If the 'SubpassDescription2'::@viewMask@ member of all elements of
--     @pSubpasses@ is @0@, @correlatedViewMaskCount@ /must/ be @0@
--
-- -   The 'SubpassDescription2'::@viewMask@ member of all elements of
--     @pSubpasses@ /must/ either all be @0@, or all not be @0@
--
-- -   If the 'SubpassDescription2'::@viewMask@ member of all elements of
--     @pSubpasses@ is @0@, the @dependencyFlags@ member of any element of
--     @pDependencies@ /must/ not include
--     'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT'
--
-- -   For any element of @pDependencies@ where its @srcSubpass@ member
--     equals its @dstSubpass@ member, if the @viewMask@ member of the
--     corresponding element of @pSubpasses@ includes more than one bit,
--     its @dependencyFlags@ member /must/ include
--     'Vulkan.Core10.Enums.DependencyFlagBits.DEPENDENCY_VIEW_LOCAL_BIT'
--
-- -   The @viewMask@ member /must/ not have a bit set at an index greater
--     than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxFramebufferLayers@
--
-- -   If the @attachment@ member of any element of the @pInputAttachments@
--     member of any element of @pSubpasses@ is not
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED', the @aspectMask@
--     member of that element of @pInputAttachments@ /must/ only include
--     aspects that are present in images of the format specified by the
--     element of @pAttachments@ specified by @attachment@
--
-- -   The @srcSubpass@ member of each element of @pDependencies@ /must/ be
--     less than @subpassCount@
--
-- -   The @dstSubpass@ member of each element of @pDependencies@ /must/ be
--     less than @subpassCount@
--
-- -   If any element of @pAttachmentImageInfos@ is used as a fragment
--     shading rate attachment in any subpass, it /must/ not be used as any
--     other attachment in the render pass
--
-- -   If @flags@ includes
--     'Vulkan.Core10.Enums.RenderPassCreateFlagBits.RENDER_PASS_CREATE_TRANSFORM_BIT_QCOM',
--     an element of @pSubpasses@ includes an instance of
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.FragmentShadingRateAttachmentInfoKHR'
--     in its @pNext@ chain, and the @pFragmentShadingRateAttachment@
--     member of that structure is not equal to @NULL@, the @attachment@
--     member of @pFragmentShadingRateAttachment@ /must/ be
--     'Vulkan.Core10.APIConstants.ATTACHMENT_UNUSED'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_fragment_density_map.RenderPassFragmentDensityMapCreateInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.RenderPassCreateFlagBits.RenderPassCreateFlagBits'
--     values
--
-- -   If @attachmentCount@ is not @0@, @pAttachments@ /must/ be a valid
--     pointer to an array of @attachmentCount@ valid
--     'AttachmentDescription2' structures
--
-- -   @pSubpasses@ /must/ be a valid pointer to an array of @subpassCount@
--     valid 'SubpassDescription2' structures
--
-- -   If @dependencyCount@ is not @0@, @pDependencies@ /must/ be a valid
--     pointer to an array of @dependencyCount@ valid 'SubpassDependency2'
--     structures
--
-- -   If @correlatedViewMaskCount@ is not @0@, @pCorrelatedViewMasks@
--     /must/ be a valid pointer to an array of @correlatedViewMaskCount@
--     @uint32_t@ values
--
-- -   @subpassCount@ /must/ be greater than @0@
--
-- = See Also
--
-- 'AttachmentDescription2',
-- 'Vulkan.Core10.Enums.RenderPassCreateFlagBits.RenderPassCreateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'SubpassDependency2',
-- 'SubpassDescription2', 'createRenderPass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.createRenderPass2KHR'
data RenderPassCreateInfo2 (es :: [Type]) = RenderPassCreateInfo2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    RenderPassCreateInfo2 es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    RenderPassCreateInfo2 es -> RenderPassCreateFlags
flags :: RenderPassCreateFlags
  , -- | @pAttachments@ is a pointer to an array of @attachmentCount@
    -- 'AttachmentDescription2' structures describing the attachments used by
    -- the render pass.
    RenderPassCreateInfo2 es
-> Vector (SomeStruct AttachmentDescription2)
attachments :: Vector (SomeStruct AttachmentDescription2)
  , -- | @pSubpasses@ is a pointer to an array of @subpassCount@
    -- 'SubpassDescription2' structures describing each subpass.
    RenderPassCreateInfo2 es -> Vector (SomeStruct SubpassDescription2)
subpasses :: Vector (SomeStruct SubpassDescription2)
  , -- | @pDependencies@ is a pointer to an array of @dependencyCount@
    -- 'SubpassDependency2' structures describing dependencies between pairs of
    -- subpasses.
    RenderPassCreateInfo2 es -> Vector SubpassDependency2
dependencies :: Vector SubpassDependency2
  , -- | @pCorrelatedViewMasks@ is a pointer to an array of view masks indicating
    -- sets of views that /may/ be more efficient to render concurrently.
    RenderPassCreateInfo2 es -> Vector Word32
correlatedViewMasks :: Vector Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RenderPassCreateInfo2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (RenderPassCreateInfo2 es)

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

instance (Extendss RenderPassCreateInfo2 es, PokeChain es) => ToCStruct (RenderPassCreateInfo2 es) where
  withCStruct :: RenderPassCreateInfo2 es
-> (Ptr (RenderPassCreateInfo2 es) -> IO b) -> IO b
withCStruct x :: RenderPassCreateInfo2 es
x f :: Ptr (RenderPassCreateInfo2 es) -> IO b
f = Int -> Int -> (Ptr (RenderPassCreateInfo2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 80 8 ((Ptr (RenderPassCreateInfo2 es) -> IO b) -> IO b)
-> (Ptr (RenderPassCreateInfo2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (RenderPassCreateInfo2 es)
p -> Ptr (RenderPassCreateInfo2 es)
-> RenderPassCreateInfo2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (RenderPassCreateInfo2 es)
p RenderPassCreateInfo2 es
x (Ptr (RenderPassCreateInfo2 es) -> IO b
f Ptr (RenderPassCreateInfo2 es)
p)
  pokeCStruct :: Ptr (RenderPassCreateInfo2 es)
-> RenderPassCreateInfo2 es -> IO b -> IO b
pokeCStruct p :: Ptr (RenderPassCreateInfo2 es)
p RenderPassCreateInfo2{..} 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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2)
    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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 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 RenderPassCreateFlags -> RenderPassCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr RenderPassCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr RenderPassCreateFlags)) (RenderPassCreateFlags
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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector (SomeStruct AttachmentDescription2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentDescription2) -> Int)
-> Vector (SomeStruct AttachmentDescription2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct AttachmentDescription2)
attachments)) :: Word32))
    Ptr (AttachmentDescription2 Any)
pPAttachments' <- ((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (AttachmentDescription2 Any)))
-> ((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentDescription2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentDescription2 _) ((Vector (SomeStruct AttachmentDescription2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct AttachmentDescription2)
attachments)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 56) 8
    (Int -> SomeStruct AttachmentDescription2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentDescription2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentDescription2
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 AttachmentDescription2)
-> SomeStruct AttachmentDescription2 -> 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 (AttachmentDescription2 Any)
-> Ptr (SomeStruct AttachmentDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentDescription2 Any)
pPAttachments' Ptr (AttachmentDescription2 Any)
-> Int -> Ptr (AttachmentDescription2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentDescription2 _))) (SomeStruct AttachmentDescription2
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 AttachmentDescription2)
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 (AttachmentDescription2 Any))
-> Ptr (AttachmentDescription2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (AttachmentDescription2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (AttachmentDescription2 _)))) (Ptr (AttachmentDescription2 Any)
pPAttachments')
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector (SomeStruct SubpassDescription2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct SubpassDescription2) -> Int)
-> Vector (SomeStruct SubpassDescription2) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct SubpassDescription2)
subpasses)) :: Word32))
    Ptr (SubpassDescription2 Any)
pPSubpasses' <- ((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (SubpassDescription2 Any)))
-> ((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (SubpassDescription2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(SubpassDescription2 _) ((Vector (SomeStruct SubpassDescription2) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct SubpassDescription2)
subpasses)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 88) 8
    (Int -> SomeStruct SubpassDescription2 -> ContT b IO ())
-> Vector (SomeStruct SubpassDescription2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct SubpassDescription2
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 SubpassDescription2)
-> SomeStruct SubpassDescription2 -> 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 (SubpassDescription2 Any)
-> Ptr (SomeStruct SubpassDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (SubpassDescription2 Any)
pPSubpasses' Ptr (SubpassDescription2 Any) -> Int -> Ptr (SubpassDescription2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (88 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (SubpassDescription2 _))) (SomeStruct SubpassDescription2
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 SubpassDescription2)
subpasses)
    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 (SubpassDescription2 Any))
-> Ptr (SubpassDescription2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (SubpassDescription2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (SubpassDescription2 _)))) (Ptr (SubpassDescription2 Any)
pPSubpasses')
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector SubpassDependency2 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SubpassDependency2 -> Int)
-> Vector SubpassDependency2 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector SubpassDependency2
dependencies)) :: Word32))
    Ptr SubpassDependency2
pPDependencies' <- ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SubpassDependency2 -> IO b) -> IO b)
 -> ContT b IO (Ptr SubpassDependency2))
-> ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SubpassDependency2 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SubpassDependency2 ((Vector SubpassDependency2 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector SubpassDependency2
dependencies)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) 8
    (Int -> SubpassDependency2 -> ContT b IO ())
-> Vector SubpassDependency2 -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SubpassDependency2
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 SubpassDependency2 -> SubpassDependency2 -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SubpassDependency2
pPDependencies' Ptr SubpassDependency2 -> Int -> Ptr SubpassDependency2
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDependency2) (SubpassDependency2
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 SubpassDependency2
dependencies)
    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 SubpassDependency2) -> Ptr SubpassDependency2 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr SubpassDependency2)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SubpassDependency2))) (Ptr SubpassDependency2
pPDependencies')
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32 -> Int) -> Vector Word32 -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Word32
correlatedViewMasks)) :: Word32))
    Ptr Word32
pPCorrelatedViewMasks' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Word32 -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Word32
correlatedViewMasks)) 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 -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPCorrelatedViewMasks' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
correlatedViewMasks)
    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 Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32))) (Ptr Word32
pPCorrelatedViewMasks')
    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 = 80
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (RenderPassCreateInfo2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (RenderPassCreateInfo2 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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2)
    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 (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    Ptr (AttachmentDescription2 Any)
pPAttachments' <- ((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (AttachmentDescription2 Any)))
-> ((Ptr (AttachmentDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (AttachmentDescription2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (AttachmentDescription2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AttachmentDescription2 _) ((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
* 56) 8
    (Int -> SomeStruct AttachmentDescription2 -> ContT b IO ())
-> Vector (SomeStruct AttachmentDescription2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AttachmentDescription2
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 AttachmentDescription2)
-> SomeStruct AttachmentDescription2 -> 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 (AttachmentDescription2 Any)
-> Ptr (SomeStruct AttachmentDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AttachmentDescription2 Any)
pPAttachments' Ptr (AttachmentDescription2 Any)
-> Int -> Ptr (AttachmentDescription2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentDescription2 _))) (SomeStruct AttachmentDescription2
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 AttachmentDescription2)
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 (AttachmentDescription2 Any))
-> Ptr (AttachmentDescription2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (AttachmentDescription2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (AttachmentDescription2 _)))) (Ptr (AttachmentDescription2 Any)
pPAttachments')
    Ptr (SubpassDescription2 Any)
pPSubpasses' <- ((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (SubpassDescription2 Any)))
-> ((Ptr (SubpassDescription2 Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (SubpassDescription2 Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (SubpassDescription2 Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(SubpassDescription2 _) ((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
* 88) 8
    (Int -> SomeStruct SubpassDescription2 -> ContT b IO ())
-> Vector (SomeStruct SubpassDescription2) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct SubpassDescription2
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 SubpassDescription2)
-> SomeStruct SubpassDescription2 -> 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 (SubpassDescription2 Any)
-> Ptr (SomeStruct SubpassDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (SubpassDescription2 Any)
pPSubpasses' Ptr (SubpassDescription2 Any) -> Int -> Ptr (SubpassDescription2 _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (88 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (SubpassDescription2 _))) (SomeStruct SubpassDescription2
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 SubpassDescription2)
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 (SubpassDescription2 Any))
-> Ptr (SubpassDescription2 Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (SubpassDescription2 _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (SubpassDescription2 _)))) (Ptr (SubpassDescription2 Any)
pPSubpasses')
    Ptr SubpassDependency2
pPDependencies' <- ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr SubpassDependency2 -> IO b) -> IO b)
 -> ContT b IO (Ptr SubpassDependency2))
-> ((Ptr SubpassDependency2 -> IO b) -> IO b)
-> ContT b IO (Ptr SubpassDependency2)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr SubpassDependency2 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @SubpassDependency2 ((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 -> SubpassDependency2 -> ContT b IO ())
-> Vector SubpassDependency2 -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SubpassDependency2
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 SubpassDependency2 -> SubpassDependency2 -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr SubpassDependency2
pPDependencies' Ptr SubpassDependency2 -> Int -> Ptr SubpassDependency2
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDependency2) (SubpassDependency2
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 SubpassDependency2
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 SubpassDependency2) -> Ptr SubpassDependency2 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr SubpassDependency2)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SubpassDependency2))) (Ptr SubpassDependency2
pPDependencies')
    Ptr Word32
pPCorrelatedViewMasks' <- ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32))
-> ((Ptr Word32 -> IO b) -> IO b) -> ContT b IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Word32 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((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 -> Word32 -> IO ()) -> Vector Word32 -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Word32
e -> Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word32
pPCorrelatedViewMasks' Ptr Word32 -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) (Word32
e)) (Vector Word32
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 Word32) -> Ptr Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32))) (Ptr Word32
pPCorrelatedViewMasks')
    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 RenderPassCreateInfo2 es, PeekChain es) => FromCStruct (RenderPassCreateInfo2 es) where
  peekCStruct :: Ptr (RenderPassCreateInfo2 es) -> IO (RenderPassCreateInfo2 es)
peekCStruct p :: Ptr (RenderPassCreateInfo2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 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)
    RenderPassCreateFlags
flags <- Ptr RenderPassCreateFlags -> IO RenderPassCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @RenderPassCreateFlags ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr RenderPassCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr RenderPassCreateFlags))
    Word32
attachmentCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr (AttachmentDescription2 Any)
pAttachments <- Ptr (Ptr (AttachmentDescription2 Any))
-> IO (Ptr (AttachmentDescription2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (AttachmentDescription2 _)) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (AttachmentDescription2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (AttachmentDescription2 a))))
    Vector (SomeStruct AttachmentDescription2)
pAttachments' <- Int
-> (Int -> IO (SomeStruct AttachmentDescription2))
-> IO (Vector (SomeStruct AttachmentDescription2))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
attachmentCount) (\i :: Int
i -> Ptr (SomeStruct AttachmentDescription2)
-> IO (SomeStruct AttachmentDescription2)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (AttachmentDescription2 Any)
-> Ptr (SomeStruct AttachmentDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (AttachmentDescription2 Any)
pAttachments Ptr (AttachmentDescription2 Any)
-> Int -> Ptr (AttachmentDescription2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AttachmentDescription2 _)))))
    Word32
subpassCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr (SubpassDescription2 Any)
pSubpasses <- Ptr (Ptr (SubpassDescription2 Any))
-> IO (Ptr (SubpassDescription2 Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (SubpassDescription2 _)) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr (SubpassDescription2 a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (SubpassDescription2 a))))
    Vector (SomeStruct SubpassDescription2)
pSubpasses' <- Int
-> (Int -> IO (SomeStruct SubpassDescription2))
-> IO (Vector (SomeStruct SubpassDescription2))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
subpassCount) (\i :: Int
i -> Ptr (SomeStruct SubpassDescription2)
-> IO (SomeStruct SubpassDescription2)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (SubpassDescription2 Any)
-> Ptr (SomeStruct SubpassDescription2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (SubpassDescription2 Any)
pSubpasses Ptr (SubpassDescription2 Any)
-> Int -> Ptr (SubpassDescription2 Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (88 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (SubpassDescription2 _)))))
    Word32
dependencyCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    Ptr SubpassDependency2
pDependencies <- Ptr (Ptr SubpassDependency2) -> IO (Ptr SubpassDependency2)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SubpassDependency2) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es)
-> Int -> Ptr (Ptr SubpassDependency2)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr SubpassDependency2)))
    Vector SubpassDependency2
pDependencies' <- Int
-> (Int -> IO SubpassDependency2) -> IO (Vector SubpassDependency2)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
dependencyCount) (\i :: Int
i -> Ptr SubpassDependency2 -> IO SubpassDependency2
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SubpassDependency2 ((Ptr SubpassDependency2
pDependencies Ptr SubpassDependency2 -> Int -> Ptr SubpassDependency2
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SubpassDependency2)))
    Word32
correlatedViewMaskCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
    Ptr Word32
pCorrelatedViewMasks <- Ptr (Ptr Word32) -> IO (Ptr Word32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) ((Ptr (RenderPassCreateInfo2 es)
p Ptr (RenderPassCreateInfo2 es) -> Int -> Ptr (Ptr Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr Word32)))
    Vector Word32
pCorrelatedViewMasks' <- Int -> (Int -> IO Word32) -> IO (Vector Word32)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
correlatedViewMaskCount) (\i :: Int
i -> Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr Word32
pCorrelatedViewMasks Ptr Word32 -> Int -> Ptr Word32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    RenderPassCreateInfo2 es -> IO (RenderPassCreateInfo2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RenderPassCreateInfo2 es -> IO (RenderPassCreateInfo2 es))
-> RenderPassCreateInfo2 es -> IO (RenderPassCreateInfo2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> RenderPassCreateFlags
-> Vector (SomeStruct AttachmentDescription2)
-> Vector (SomeStruct SubpassDescription2)
-> Vector SubpassDependency2
-> Vector Word32
-> RenderPassCreateInfo2 es
forall (es :: [*]).
Chain es
-> RenderPassCreateFlags
-> Vector (SomeStruct AttachmentDescription2)
-> Vector (SomeStruct SubpassDescription2)
-> Vector SubpassDependency2
-> Vector Word32
-> RenderPassCreateInfo2 es
RenderPassCreateInfo2
             Chain es
next RenderPassCreateFlags
flags Vector (SomeStruct AttachmentDescription2)
pAttachments' Vector (SomeStruct SubpassDescription2)
pSubpasses' Vector SubpassDependency2
pDependencies' Vector Word32
pCorrelatedViewMasks'

instance es ~ '[] => Zero (RenderPassCreateInfo2 es) where
  zero :: RenderPassCreateInfo2 es
zero = Chain es
-> RenderPassCreateFlags
-> Vector (SomeStruct AttachmentDescription2)
-> Vector (SomeStruct SubpassDescription2)
-> Vector SubpassDependency2
-> Vector Word32
-> RenderPassCreateInfo2 es
forall (es :: [*]).
Chain es
-> RenderPassCreateFlags
-> Vector (SomeStruct AttachmentDescription2)
-> Vector (SomeStruct SubpassDescription2)
-> Vector SubpassDependency2
-> Vector Word32
-> RenderPassCreateInfo2 es
RenderPassCreateInfo2
           ()
           RenderPassCreateFlags
forall a. Zero a => a
zero
           Vector (SomeStruct AttachmentDescription2)
forall a. Monoid a => a
mempty
           Vector (SomeStruct SubpassDescription2)
forall a. Monoid a => a
mempty
           Vector SubpassDependency2
forall a. Monoid a => a
mempty
           Vector Word32
forall a. Monoid a => a
mempty


-- | VkSubpassBeginInfo - Structure specifying subpass begin info
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Core10.Enums.SubpassContents.SubpassContents',
-- 'cmdBeginRenderPass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.cmdBeginRenderPass2KHR',
-- 'cmdNextSubpass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.cmdNextSubpass2KHR'
data SubpassBeginInfo = SubpassBeginInfo
  { -- | @contents@ is a 'Vulkan.Core10.Enums.SubpassContents.SubpassContents'
    -- value specifying how the commands in the next subpass will be provided.
    --
    -- @contents@ /must/ be a valid
    -- 'Vulkan.Core10.Enums.SubpassContents.SubpassContents' value
    SubpassBeginInfo -> SubpassContents
contents :: SubpassContents }
  deriving (Typeable, SubpassBeginInfo -> SubpassBeginInfo -> Bool
(SubpassBeginInfo -> SubpassBeginInfo -> Bool)
-> (SubpassBeginInfo -> SubpassBeginInfo -> Bool)
-> Eq SubpassBeginInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubpassBeginInfo -> SubpassBeginInfo -> Bool
$c/= :: SubpassBeginInfo -> SubpassBeginInfo -> Bool
== :: SubpassBeginInfo -> SubpassBeginInfo -> Bool
$c== :: SubpassBeginInfo -> SubpassBeginInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SubpassBeginInfo)
#endif
deriving instance Show SubpassBeginInfo

instance ToCStruct SubpassBeginInfo where
  withCStruct :: SubpassBeginInfo
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b) -> IO b
withCStruct x :: SubpassBeginInfo
x f :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b
f = Int
-> Int
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b) -> IO b)
-> (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p -> ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> SubpassBeginInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p SubpassBeginInfo
x (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b
f "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p)
  pokeCStruct :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> SubpassBeginInfo -> IO b -> IO b
pokeCStruct p :: "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p SubpassBeginInfo{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_BEGIN_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr SubpassContents -> SubpassContents -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr SubpassContents
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SubpassContents)) (SubpassContents
contents)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo) -> IO b -> IO b
pokeZeroCStruct p :: "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_BEGIN_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr SubpassContents -> SubpassContents -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr SubpassContents
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SubpassContents)) (SubpassContents
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct SubpassBeginInfo where
  peekCStruct :: ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> IO SubpassBeginInfo
peekCStruct p :: "pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p = do
    SubpassContents
contents <- Ptr SubpassContents -> IO SubpassContents
forall a. Storable a => Ptr a -> IO a
peek @SubpassContents (("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo
p ("pSubpassBeginInfo" ::: Ptr SubpassBeginInfo)
-> Int -> Ptr SubpassContents
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SubpassContents))
    SubpassBeginInfo -> IO SubpassBeginInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassBeginInfo -> IO SubpassBeginInfo)
-> SubpassBeginInfo -> IO SubpassBeginInfo
forall a b. (a -> b) -> a -> b
$ SubpassContents -> SubpassBeginInfo
SubpassBeginInfo
             SubpassContents
contents

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

instance Zero SubpassBeginInfo where
  zero :: SubpassBeginInfo
zero = SubpassContents -> SubpassBeginInfo
SubpassBeginInfo
           SubpassContents
forall a. Zero a => a
zero


-- | VkSubpassEndInfo - Structure specifying subpass end info
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'cmdEndRenderPass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.cmdEndRenderPass2KHR',
-- 'cmdNextSubpass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.cmdNextSubpass2KHR'
data SubpassEndInfo = SubpassEndInfo
  {}
  deriving (Typeable, SubpassEndInfo -> SubpassEndInfo -> Bool
(SubpassEndInfo -> SubpassEndInfo -> Bool)
-> (SubpassEndInfo -> SubpassEndInfo -> Bool) -> Eq SubpassEndInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubpassEndInfo -> SubpassEndInfo -> Bool
$c/= :: SubpassEndInfo -> SubpassEndInfo -> Bool
== :: SubpassEndInfo -> SubpassEndInfo -> Bool
$c== :: SubpassEndInfo -> SubpassEndInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SubpassEndInfo)
#endif
deriving instance Show SubpassEndInfo

instance ToCStruct SubpassEndInfo where
  withCStruct :: SubpassEndInfo
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b) -> IO b
withCStruct x :: SubpassEndInfo
x f :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b
f = Int
-> Int
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 8 ((("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b) -> IO b)
-> (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p -> ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> SubpassEndInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p SubpassEndInfo
x (("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b
f "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p)
  pokeCStruct :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> SubpassEndInfo -> IO b -> IO b
pokeCStruct p :: "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p SubpassEndInfo f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassEndInfo" ::: Ptr SubpassEndInfo
p ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_END_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassEndInfo" ::: Ptr SubpassEndInfo
p ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO b -> IO b
pokeZeroCStruct p :: "pSubpassEndInfo" ::: Ptr SubpassEndInfo
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassEndInfo" ::: Ptr SubpassEndInfo
p ("pSubpassEndInfo" ::: Ptr SubpassEndInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBPASS_END_INFO)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSubpassEndInfo" ::: Ptr SubpassEndInfo
p ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct SubpassEndInfo where
  peekCStruct :: ("pSubpassEndInfo" ::: Ptr SubpassEndInfo) -> IO SubpassEndInfo
peekCStruct _ = SubpassEndInfo -> IO SubpassEndInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubpassEndInfo -> IO SubpassEndInfo)
-> SubpassEndInfo -> IO SubpassEndInfo
forall a b. (a -> b) -> a -> b
$ SubpassEndInfo
SubpassEndInfo
                           

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

instance Zero SubpassEndInfo where
  zero :: SubpassEndInfo
zero = SubpassEndInfo
SubpassEndInfo