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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Attachment
       (VkAttachmentDescription, VkAttachmentReference,
        VkAttachmentSampleLocationsEXT)
       where
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.Enum.Attachment       (VkAttachmentDescriptionFlags,
                                                    VkAttachmentLoadOp,
                                                    VkAttachmentStoreOp)
import Graphics.Vulkan.Types.Enum.Format           (VkFormat)
import Graphics.Vulkan.Types.Enum.Image            (VkImageLayout)
import Graphics.Vulkan.Types.Enum.SampleCountFlags (VkSampleCountFlagBits)
import Graphics.Vulkan.Types.Struct.SampleLocation (VkSampleLocationsInfoEXT)

-- | > typedef struct VkAttachmentDescription {
--   >     VkAttachmentDescriptionFlags flags;
--   >     VkFormat               format;
--   >     VkSampleCountFlagBits  samples;
--   >     VkAttachmentLoadOp     loadOp;
--   >     VkAttachmentStoreOp    storeOp;
--   >     VkAttachmentLoadOp     stencilLoadOp;
--   >     VkAttachmentStoreOp    stencilStoreOp;
--   >     VkImageLayout          initialLayout;
--   >     VkImageLayout          finalLayout;
--   > } VkAttachmentDescription;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkAttachmentDescription VkAttachmentDescription registry at www.khronos.org>
type VkAttachmentDescription = VkStruct VkAttachmentDescription' -- ' closing tick for hsc2hs

data VkAttachmentDescription' -- ' closing tick for hsc2hs

instance VulkanMarshal VkAttachmentDescription where
    type StructRep VkAttachmentDescription =
         'StructMeta "VkAttachmentDescription" VkAttachmentDescription -- ' closing tick for hsc2hs
           (36)
{-# LINE 43 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
           4
{-# LINE 44 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
           '[('FieldMeta "flags" VkAttachmentDescriptionFlags 'True  -- ' closing tick for hsc2hs
                                                                    (0)
{-# LINE 46 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "format" VkFormat 'False
                                                  (4)
{-# LINE 51 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "samples" VkSampleCountFlagBits 'False
                                                                (8)
{-# LINE 56 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "loadOp" VkAttachmentLoadOp 'False
                                                            (12)
{-# LINE 61 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "storeOp" VkAttachmentStoreOp 'False
                                                              (16)
{-# LINE 66 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "stencilLoadOp" VkAttachmentLoadOp 'False
                                                                   (20)
{-# LINE 71 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "stencilStoreOp" VkAttachmentStoreOp 'False
                                                                     (24)
{-# LINE 76 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "initialLayout" VkImageLayout 'False
                                                              (28)
{-# LINE 81 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "finalLayout" VkImageLayout 'False
                                                            (32)
{-# LINE 86 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.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 VkAttachmentReference {
--   >     uint32_t               attachment;
--   >     VkImageLayout          layout;
--   > } VkAttachmentReference;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkAttachmentReference VkAttachmentReference registry at www.khronos.org>
type VkAttachmentReference = VkStruct VkAttachmentReference' -- ' closing tick for hsc2hs

data VkAttachmentReference' -- ' closing tick for hsc2hs

instance VulkanMarshal VkAttachmentReference where
    type StructRep VkAttachmentReference =
         'StructMeta "VkAttachmentReference" VkAttachmentReference  -- ' closing tick for hsc2hs
                                                                   (8)
{-# LINE 107 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
           4
{-# LINE 108 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
           '[('FieldMeta "attachment" Word32 'False  -- ' closing tick for hsc2hs
                                                    (0)
{-# LINE 110 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "layout" VkImageLayout 'False
                                                       (4)
{-# LINE 115 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.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 VkAttachmentSampleLocationsEXT {
--   >     uint32_t                         attachmentIndex;
--   >     VkSampleLocationsInfoEXT         sampleLocationsInfo;
--   > } VkAttachmentSampleLocationsEXT;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkAttachmentSampleLocationsEXT VkAttachmentSampleLocationsEXT registry at www.khronos.org>
type VkAttachmentSampleLocationsEXT =
     VkStruct VkAttachmentSampleLocationsEXT' -- ' closing tick for hsc2hs

data VkAttachmentSampleLocationsEXT' -- ' closing tick for hsc2hs

instance VulkanMarshal VkAttachmentSampleLocationsEXT where
    type StructRep VkAttachmentSampleLocationsEXT =
         'StructMeta "VkAttachmentSampleLocationsEXT" -- ' closing tick for hsc2hs
           VkAttachmentSampleLocationsEXT
           (48)
{-# LINE 138 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
           8
{-# LINE 139 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
           '[('FieldMeta "attachmentIndex" Word32 'False  -- ' closing tick for hsc2hs
                                                         (0)
{-# LINE 141 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
                1
                'True -- ' closing tick for hsc2hs
                'True), -- ' closing tick for hsc2hs
             ('FieldMeta "sampleLocationsInfo" VkSampleLocationsInfoEXT 'False
                (8)
{-# LINE 146 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.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