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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Subpass
       (VkSubpassDependency, VkSubpassDescription,
        VkSubpassSampleLocationsEXT)
       where
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.Enum.AccessFlags      (VkAccessFlags)
import Graphics.Vulkan.Types.Enum.DependencyFlags  (VkDependencyFlags)
import Graphics.Vulkan.Types.Enum.Pipeline         (VkPipelineBindPoint,
                                                    VkPipelineStageFlags)
import Graphics.Vulkan.Types.Enum.Subpass          (VkSubpassDescriptionFlags)
import Graphics.Vulkan.Types.Struct.Attachment     (VkAttachmentReference)
import Graphics.Vulkan.Types.Struct.SampleLocation (VkSampleLocationsInfoEXT)

-- | > typedef struct VkSubpassDependency {
--   >     uint32_t               srcSubpass;
--   >     uint32_t               dstSubpass;
--   >     VkPipelineStageFlags   srcStageMask;
--   >     VkPipelineStageFlags   dstStageMask;
--   >     VkAccessFlags          srcAccessMask;
--   >     VkAccessFlags          dstAccessMask;
--   >     VkDependencyFlags      dependencyFlags;
--   > } VkSubpassDependency;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkSubpassDependency VkSubpassDependency registry at www.khronos.org>
type VkSubpassDependency = VkStruct VkSubpassDependency' -- ' closing tick for hsc2hs

data VkSubpassDependency' -- ' closing tick for hsc2hs

instance VulkanMarshal VkSubpassDependency where
    type StructRep VkSubpassDependency =
         'StructMeta "VkSubpassDependency" VkSubpassDependency  -- ' closing tick for hsc2hs
                                                               (28)
{-# LINE 41 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
           4
{-# LINE 42 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
           '[('FieldMeta "srcSubpass" Word32 'False  -- ' closing tick for hsc2hs
                                                    (0)
{-# LINE 44 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "dstSubpass" Word32 'False
                                                    (4)
{-# LINE 49 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "srcStageMask" VkPipelineStageFlags 'False
                                                                    (8)
{-# LINE 54 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "dstStageMask" VkPipelineStageFlags 'False
                                                                    (12)
{-# LINE 59 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "srcAccessMask" VkAccessFlags 'True
                                                             (16)
{-# LINE 64 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "dstAccessMask" VkAccessFlags 'True
                                                             (20)
{-# LINE 69 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "dependencyFlags" VkDependencyFlags 'True
                                                                   (24)
{-# LINE 74 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.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 VkSubpassDescription {
--   >     VkSubpassDescriptionFlags flags;
--   >     VkPipelineBindPoint    pipelineBindPoint;
--   >     uint32_t               inputAttachmentCount;
--   >     const VkAttachmentReference* pInputAttachments;
--   >     uint32_t               colorAttachmentCount;
--   >     const VkAttachmentReference* pColorAttachments;
--   >     const VkAttachmentReference* pResolveAttachments;
--   >     const VkAttachmentReference* pDepthStencilAttachment;
--   >     uint32_t               preserveAttachmentCount;
--   >     const uint32_t* pPreserveAttachments;
--   > } VkSubpassDescription;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkSubpassDescription VkSubpassDescription registry at www.khronos.org>
type VkSubpassDescription = VkStruct VkSubpassDescription' -- ' closing tick for hsc2hs

data VkSubpassDescription' -- ' closing tick for hsc2hs

instance VulkanMarshal VkSubpassDescription where
    type StructRep VkSubpassDescription =
         'StructMeta "VkSubpassDescription" VkSubpassDescription  -- ' closing tick for hsc2hs
                                                                 (72)
{-# LINE 103 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
           8
{-# LINE 104 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
           '[('FieldMeta "flags" VkSubpassDescriptionFlags 'True  -- ' closing tick for hsc2hs
                                                                 (0)
{-# LINE 106 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pipelineBindPoint" VkPipelineBindPoint 'False
                (4)
{-# LINE 111 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "inputAttachmentCount" Word32 'True
                                                             (8)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pInputAttachments" (Ptr VkAttachmentReference) 'False
                (16)
{-# LINE 121 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "colorAttachmentCount" Word32 'True
                                                             (24)
{-# LINE 126 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pColorAttachments" (Ptr VkAttachmentReference) 'False
                (32)
{-# LINE 131 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pResolveAttachments" (Ptr VkAttachmentReference) 'True
                (40)
{-# LINE 136 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pDepthStencilAttachment" (Ptr VkAttachmentReference) -- ' closing tick for hsc2hs
                'True -- ' closing tick for hsc2hs
                (48)
{-# LINE 142 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "preserveAttachmentCount" Word32 'True
                                                                (56)
{-# LINE 147 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "pPreserveAttachments" (Ptr Word32) 'False
                                                                    (64)
{-# LINE 152 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.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 VkSubpassSampleLocationsEXT {
--   >     uint32_t                         subpassIndex;
--   >     VkSampleLocationsInfoEXT         sampleLocationsInfo;
--   > } VkSubpassSampleLocationsEXT;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkSubpassSampleLocationsEXT VkSubpassSampleLocationsEXT registry at www.khronos.org>
type VkSubpassSampleLocationsEXT =
     VkStruct VkSubpassSampleLocationsEXT' -- ' closing tick for hsc2hs

data VkSubpassSampleLocationsEXT' -- ' closing tick for hsc2hs

instance VulkanMarshal VkSubpassSampleLocationsEXT where
    type StructRep VkSubpassSampleLocationsEXT =
         'StructMeta "VkSubpassSampleLocationsEXT" -- ' closing tick for hsc2hs
           VkSubpassSampleLocationsEXT
           (48)
{-# LINE 175 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
           8
{-# LINE 176 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
           '[('FieldMeta "subpassIndex" Word32 'False  -- ' closing tick for hsc2hs
                                                      (0)
{-# LINE 178 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "sampleLocationsInfo" VkSampleLocationsInfoEXT 'False
                (8)
{-# LINE 183 "src-gen/Graphics/Vulkan/Types/Struct/Subpass.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