{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.RenderPass
       (VkRenderPassBeginInfo, VkRenderPassCreateInfo,
        VkRenderPassInputAttachmentAspectCreateInfo,
        VkRenderPassInputAttachmentAspectCreateInfoKHR,
        VkRenderPassMultiviewCreateInfo,
        VkRenderPassMultiviewCreateInfoKHR,
        VkRenderPassSampleLocationsBeginInfoEXT)
       where
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.Bitmasks                              (VkRenderPassCreateFlags)
import Graphics.Vulkan.Types.Enum.StructureType                    (VkStructureType)
import Graphics.Vulkan.Types.Handles                               (VkFramebuffer,
                                                                    VkRenderPass)
import Graphics.Vulkan.Types.Struct.Attachment                     (VkAttachmentDescription,
                                                                    VkAttachmentSampleLocationsEXT)
import Graphics.Vulkan.Types.Struct.Clear                          (VkClearValue)
import Graphics.Vulkan.Types.Struct.InputAttachmentAspectReference (VkInputAttachmentAspectReference)
import Graphics.Vulkan.Types.Struct.Rect                           (VkRect2D)
import Graphics.Vulkan.Types.Struct.Subpass                        (VkSubpassDependency,
                                                                    VkSubpassDescription,
                                                                    VkSubpassSampleLocationsEXT)

-- | > typedef struct VkRenderPassBeginInfo {
--   >     VkStructureType sType;
--   >     const void*            pNext;
--   >     VkRenderPass           renderPass;
--   >     VkFramebuffer          framebuffer;
--   >     VkRect2D               renderArea;
--   >     uint32_t               clearValueCount;
--   >     const VkClearValue*    pClearValues;
--   > } VkRenderPassBeginInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkRenderPassBeginInfo VkRenderPassBeginInfo registry at www.khronos.org>
type VkRenderPassBeginInfo = VkStruct VkRenderPassBeginInfo' -- ' closing tick for hsc2hs

data VkRenderPassBeginInfo' -- ' closing tick for hsc2hs

instance VulkanMarshal VkRenderPassBeginInfo where
    type StructRep VkRenderPassBeginInfo =
         'StructMeta "VkRenderPassBeginInfo" VkRenderPassBeginInfo  -- ' closing tick for hsc2hs
                                                                   (64)
{-# LINE 50 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           8
{-# LINE 51 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 53 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False
                                                   (8)
{-# LINE 58 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "renderPass" VkRenderPass 'False
                                                          (16)
{-# LINE 63 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "framebuffer" VkFramebuffer 'False
                                                            (24)
{-# LINE 68 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "renderArea" VkRect2D 'False
                                                      (32)
{-# LINE 73 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "clearValueCount" Word32 'True
                                                        (48)
{-# LINE 78 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pClearValues" (Ptr VkClearValue) 'False
                                                                  (56)
{-# LINE 83 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True)] -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           '[] -- ' closing tick for hsc2hs

-- | > typedef struct VkRenderPassCreateInfo {
--   >     VkStructureType sType;
--   >     const void*            pNext;
--   >     VkRenderPassCreateFlags    flags;
--   >     uint32_t   attachmentCount;
--   >     const VkAttachmentDescription* pAttachments;
--   >     uint32_t               subpassCount;
--   >     const VkSubpassDescription* pSubpasses;
--   >     uint32_t       dependencyCount;
--   >     const VkSubpassDependency* pDependencies;
--   > } VkRenderPassCreateInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkRenderPassCreateInfo VkRenderPassCreateInfo registry at www.khronos.org>
type VkRenderPassCreateInfo = VkStruct VkRenderPassCreateInfo' -- ' closing tick for hsc2hs

data VkRenderPassCreateInfo' -- ' closing tick for hsc2hs

instance VulkanMarshal VkRenderPassCreateInfo where
    type StructRep VkRenderPassCreateInfo =
         'StructMeta "VkRenderPassCreateInfo" VkRenderPassCreateInfo -- ' closing tick for hsc2hs
           (64)
{-# LINE 111 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           8
{-# LINE 112 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 114 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False
                                                   (8)
{-# LINE 119 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "flags" VkRenderPassCreateFlags 'True
                                                               (16)
{-# LINE 124 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "attachmentCount" Word32 'True
                                                        (20)
{-# LINE 129 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pAttachments" (Ptr VkAttachmentDescription) 'False
                (24)
{-# LINE 134 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "subpassCount" Word32 'False
                                                      (32)
{-# LINE 139 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pSubpasses" (Ptr VkSubpassDescription) 'False
                (40)
{-# LINE 144 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "dependencyCount" Word32 'True
                                                        (48)
{-# LINE 149 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pDependencies" (Ptr VkSubpassDependency) 'False
                (56)
{-# LINE 154 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True)] -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           '[] -- ' closing tick for hsc2hs

-- | > typedef struct VkRenderPassInputAttachmentAspectCreateInfo {
--   >     VkStructureType sType;
--   >     const void*                     pNext;
--   >     uint32_t                        aspectReferenceCount;
--   >     const VkInputAttachmentAspectReference* pAspectReferences;
--   > } VkRenderPassInputAttachmentAspectCreateInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkRenderPassInputAttachmentAspectCreateInfo VkRenderPassInputAttachmentAspectCreateInfo registry at www.khronos.org>
type VkRenderPassInputAttachmentAspectCreateInfo =
     VkStruct VkRenderPassInputAttachmentAspectCreateInfo' -- ' closing tick for hsc2hs

data VkRenderPassInputAttachmentAspectCreateInfo' -- ' closing tick for hsc2hs

instance VulkanMarshal VkRenderPassInputAttachmentAspectCreateInfo
         where
    type StructRep VkRenderPassInputAttachmentAspectCreateInfo =
         'StructMeta "VkRenderPassInputAttachmentAspectCreateInfo" -- ' closing tick for hsc2hs
           VkRenderPassInputAttachmentAspectCreateInfo
           (32)
{-# LINE 180 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           8
{-# LINE 181 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 183 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False
                                                   (8)
{-# LINE 188 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "aspectReferenceCount" Word32 'False
                                                              (16)
{-# LINE 193 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pAspectReferences" -- ' closing tick for hsc2hs
                (Ptr VkInputAttachmentAspectReference)
                'False -- ' closing tick for hsc2hs
                (24)
{-# LINE 200 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True)] -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           '[VkRenderPassCreateInfo] -- ' closing tick for hsc2hs

-- | Alias for `VkRenderPassInputAttachmentAspectCreateInfo`
type VkRenderPassInputAttachmentAspectCreateInfoKHR =
     VkRenderPassInputAttachmentAspectCreateInfo

-- | > typedef struct VkRenderPassMultiviewCreateInfo {
--   >     VkStructureType        sType;
--   >     const void*            pNext;
--   >     uint32_t               subpassCount;
--   >     const uint32_t*     pViewMasks;
--   >     uint32_t               dependencyCount;
--   >     const int32_t*   pViewOffsets;
--   >     uint32_t               correlationMaskCount;
--   >     const uint32_t* pCorrelationMasks;
--   > } VkRenderPassMultiviewCreateInfo;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkRenderPassMultiviewCreateInfo VkRenderPassMultiviewCreateInfo registry at www.khronos.org>
type VkRenderPassMultiviewCreateInfo =
     VkStruct VkRenderPassMultiviewCreateInfo' -- ' closing tick for hsc2hs

data VkRenderPassMultiviewCreateInfo' -- ' closing tick for hsc2hs

instance VulkanMarshal VkRenderPassMultiviewCreateInfo where
    type StructRep VkRenderPassMultiviewCreateInfo =
         'StructMeta "VkRenderPassMultiviewCreateInfo" -- ' closing tick for hsc2hs
           VkRenderPassMultiviewCreateInfo
           (64)
{-# LINE 233 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           8
{-# LINE 234 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 236 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False
                                                   (8)
{-# LINE 241 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "subpassCount" Word32 'True
                                                     (16)
{-# LINE 246 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pViewMasks" (Ptr Word32) 'False
                                                          (24)
{-# LINE 251 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "dependencyCount" Word32 'True
                                                        (32)
{-# LINE 256 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pViewOffsets" (Ptr Int32) 'False
                                                           (40)
{-# LINE 261 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "correlationMaskCount" Word32 'True
                                                             (48)
{-# LINE 266 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pCorrelationMasks" (Ptr Word32) 'False
                                                                 (56)
{-# LINE 271 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True)] -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           '[VkRenderPassCreateInfo] -- ' closing tick for hsc2hs

-- | Alias for `VkRenderPassMultiviewCreateInfo`
type VkRenderPassMultiviewCreateInfoKHR =
     VkRenderPassMultiviewCreateInfo

-- | > typedef struct VkRenderPassSampleLocationsBeginInfoEXT {
--   >     VkStructureType sType;
--   >     const void*                      pNext;
--   >     uint32_t         attachmentInitialSampleLocationsCount;
--   >     const VkAttachmentSampleLocationsEXT* pAttachmentInitialSampleLocations;
--   >     uint32_t         postSubpassSampleLocationsCount;
--   >     const VkSubpassSampleLocationsEXT* pPostSubpassSampleLocations;
--   > } VkRenderPassSampleLocationsBeginInfoEXT;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkRenderPassSampleLocationsBeginInfoEXT VkRenderPassSampleLocationsBeginInfoEXT registry at www.khronos.org>
type VkRenderPassSampleLocationsBeginInfoEXT =
     VkStruct VkRenderPassSampleLocationsBeginInfoEXT' -- ' closing tick for hsc2hs

data VkRenderPassSampleLocationsBeginInfoEXT' -- ' closing tick for hsc2hs

instance VulkanMarshal VkRenderPassSampleLocationsBeginInfoEXT
         where
    type StructRep VkRenderPassSampleLocationsBeginInfoEXT =
         'StructMeta "VkRenderPassSampleLocationsBeginInfoEXT" -- ' closing tick for hsc2hs
           VkRenderPassSampleLocationsBeginInfoEXT
           (48)
{-# LINE 303 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           8
{-# LINE 304 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
           '[('FieldMeta "sType" VkStructureType 'False  -- ' closing tick for hsc2hs
                                                        (0)
{-# LINE 306 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pNext" (Ptr Void) 'False
                                                   (8)
{-# LINE 311 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "attachmentInitialSampleLocationsCount" Word32 'True
                (16)
{-# LINE 316 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pAttachmentInitialSampleLocations" -- ' closing tick for hsc2hs
                (Ptr VkAttachmentSampleLocationsEXT)
                'False -- ' closing tick for hsc2hs
                (24)
{-# LINE 323 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "postSubpassSampleLocationsCount" Word32 'True
                (32)
{-# LINE 328 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pPostSubpassSampleLocations" -- ' closing tick for hsc2hs
                (Ptr VkSubpassSampleLocationsEXT)
                'False -- ' closing tick for hsc2hs
                (40)
{-# LINE 335 "src-gen/Graphics/Vulkan/Types/Struct/RenderPass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True)] -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           'False -- ' closing tick for hsc2hs
           '[VkRenderPassBeginInfo] -- ' closing tick for hsc2hs