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

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

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Attachment
       (VkAttachmentDescription(..), VkAttachmentReference(..),
        VkAttachmentSampleLocationsEXT(..))
       where
import           Foreign.Storable                            (Storable (..))
import           GHC.Base                                    (Addr#, ByteArray#,
                                                              byteArrayContents#,
                                                              plusAddr#)
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)
import           System.IO.Unsafe                            (unsafeDupablePerformIO)

-- | > 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>
data VkAttachmentDescription = VkAttachmentDescription# Addr#
                                                        ByteArray#

instance Eq VkAttachmentDescription where
        (VkAttachmentDescription# a _) == x@(VkAttachmentDescription# b _)
          = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkAttachmentDescription where
        (VkAttachmentDescription# a _) `compare`
          x@(VkAttachmentDescription# b _) = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

instance Storable VkAttachmentDescription where
        sizeOf ~_ = (36)
{-# LINE 59 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment ~_ = (4)
{-# LINE 62 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkAttachmentDescription where
        unsafeAddr (VkAttachmentDescription# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkAttachmentDescription# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkAttachmentDescription# (plusAddr# (byteArrayContents# b) off) b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkAttachmentDescription where
        type StructFields VkAttachmentDescription =
             '["flags", "format", "samples", "loadOp", "storeOp", -- ' closing tick for hsc2hs
               "stencilLoadOp", "stencilStoreOp", "initialLayout", "finalLayout"]
        type CUnionType VkAttachmentDescription = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkAttachmentDescription = 'False -- ' closing tick for hsc2hs
        type StructExtends VkAttachmentDescription = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "flags" VkAttachmentDescription where
        type FieldType "flags" VkAttachmentDescription =
             VkAttachmentDescriptionFlags
        type FieldOptional "flags" VkAttachmentDescription = 'True -- ' closing tick for hsc2hs
        type FieldOffset "flags" VkAttachmentDescription =
             (0)
{-# LINE 98 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "flags" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset = (0)
{-# LINE 105 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "flags" VkAttachmentDescription where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 112 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "flags" VkAttachmentDescription where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 122 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "format" VkAttachmentDescription where
        type FieldType "format" VkAttachmentDescription = VkFormat
        type FieldOptional "format" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs
        type FieldOffset "format" VkAttachmentDescription =
             (4)
{-# LINE 129 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "format" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (4)
{-# LINE 136 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "format" VkAttachmentDescription where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (4))
{-# LINE 143 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (4)
{-# LINE 147 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "format" VkAttachmentDescription where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (4)
{-# LINE 153 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "samples" VkAttachmentDescription where
        type FieldType "samples" VkAttachmentDescription =
             VkSampleCountFlagBits
        type FieldOptional "samples" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs
        type FieldOffset "samples" VkAttachmentDescription =
             (8)
{-# LINE 161 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "samples" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (8)
{-# LINE 169 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "samples" VkAttachmentDescription where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 176 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (8)
{-# LINE 180 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "samples" VkAttachmentDescription where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 186 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "loadOp" VkAttachmentDescription where
        type FieldType "loadOp" VkAttachmentDescription =
             VkAttachmentLoadOp
        type FieldOptional "loadOp" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs
        type FieldOffset "loadOp" VkAttachmentDescription =
             (12)
{-# LINE 194 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "loadOp" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (12)
{-# LINE 201 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "loadOp" VkAttachmentDescription where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (12))
{-# LINE 208 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (12)
{-# LINE 212 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "loadOp" VkAttachmentDescription where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (12)
{-# LINE 218 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "storeOp" VkAttachmentDescription where
        type FieldType "storeOp" VkAttachmentDescription =
             VkAttachmentStoreOp
        type FieldOptional "storeOp" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs
        type FieldOffset "storeOp" VkAttachmentDescription =
             (16)
{-# LINE 226 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "storeOp" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (16)
{-# LINE 234 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "storeOp" VkAttachmentDescription where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 241 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (16)
{-# LINE 245 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "storeOp" VkAttachmentDescription where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 251 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "stencilLoadOp" VkAttachmentDescription where
        type FieldType "stencilLoadOp" VkAttachmentDescription =
             VkAttachmentLoadOp
        type FieldOptional "stencilLoadOp" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs
        type FieldOffset "stencilLoadOp" VkAttachmentDescription =
             (20)
{-# LINE 259 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "stencilLoadOp" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (20)
{-# LINE 267 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "stencilLoadOp" VkAttachmentDescription where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (20))
{-# LINE 274 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (20)
{-# LINE 278 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "stencilLoadOp" VkAttachmentDescription where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (20)
{-# LINE 284 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "stencilStoreOp" VkAttachmentDescription where
        type FieldType "stencilStoreOp" VkAttachmentDescription =
             VkAttachmentStoreOp
        type FieldOptional "stencilStoreOp" VkAttachmentDescription =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "stencilStoreOp" VkAttachmentDescription =
             (24)
{-# LINE 293 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "stencilStoreOp" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (24)
{-# LINE 301 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "stencilStoreOp" VkAttachmentDescription where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (24))
{-# LINE 308 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (24)
{-# LINE 312 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "stencilStoreOp" VkAttachmentDescription where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (24)
{-# LINE 318 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "initialLayout" VkAttachmentDescription where
        type FieldType "initialLayout" VkAttachmentDescription =
             VkImageLayout
        type FieldOptional "initialLayout" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs
        type FieldOffset "initialLayout" VkAttachmentDescription =
             (28)
{-# LINE 326 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "initialLayout" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (28)
{-# LINE 334 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "initialLayout" VkAttachmentDescription where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (28))
{-# LINE 341 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (28)
{-# LINE 345 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "initialLayout" VkAttachmentDescription where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (28)
{-# LINE 351 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "finalLayout" VkAttachmentDescription where
        type FieldType "finalLayout" VkAttachmentDescription =
             VkImageLayout
        type FieldOptional "finalLayout" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs
        type FieldOffset "finalLayout" VkAttachmentDescription =
             (32)
{-# LINE 359 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "finalLayout" VkAttachmentDescription = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (32)
{-# LINE 367 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "finalLayout" VkAttachmentDescription where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (32))
{-# LINE 374 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (32)
{-# LINE 378 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "finalLayout" VkAttachmentDescription where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (32)
{-# LINE 384 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance Show VkAttachmentDescription where
        showsPrec d x
          = showString "VkAttachmentDescription {" .
              showString "flags = " .
                showsPrec d (getField @"flags" x) .
                  showString ", " .
                    showString "format = " .
                      showsPrec d (getField @"format" x) .
                        showString ", " .
                          showString "samples = " .
                            showsPrec d (getField @"samples" x) .
                              showString ", " .
                                showString "loadOp = " .
                                  showsPrec d (getField @"loadOp" x) .
                                    showString ", " .
                                      showString "storeOp = " .
                                        showsPrec d (getField @"storeOp" x) .
                                          showString ", " .
                                            showString "stencilLoadOp = " .
                                              showsPrec d (getField @"stencilLoadOp" x) .
                                                showString ", " .
                                                  showString "stencilStoreOp = " .
                                                    showsPrec d (getField @"stencilStoreOp" x) .
                                                      showString ", " .
                                                        showString "initialLayout = " .
                                                          showsPrec d (getField @"initialLayout" x)
                                                            .
                                                            showString ", " .
                                                              showString "finalLayout = " .
                                                                showsPrec d
                                                                  (getField @"finalLayout" x)
                                                                  . showChar '}'

-- | > 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>
data VkAttachmentReference = VkAttachmentReference# Addr#
                                                    ByteArray#

instance Eq VkAttachmentReference where
        (VkAttachmentReference# a _) == x@(VkAttachmentReference# b _)
          = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkAttachmentReference where
        (VkAttachmentReference# a _) `compare`
          x@(VkAttachmentReference# b _) = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

instance Storable VkAttachmentReference where
        sizeOf ~_ = (8)
{-# LINE 441 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment ~_ = (4)
{-# LINE 444 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkAttachmentReference where
        unsafeAddr (VkAttachmentReference# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkAttachmentReference# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkAttachmentReference# (plusAddr# (byteArrayContents# b) off) b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkAttachmentReference where
        type StructFields VkAttachmentReference = '["attachment", "layout"] -- ' closing tick for hsc2hs
        type CUnionType VkAttachmentReference = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkAttachmentReference = 'False -- ' closing tick for hsc2hs
        type StructExtends VkAttachmentReference = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "attachment" VkAttachmentReference where
        type FieldType "attachment" VkAttachmentReference = Word32
        type FieldOptional "attachment" VkAttachmentReference = 'False -- ' closing tick for hsc2hs
        type FieldOffset "attachment" VkAttachmentReference =
             (0)
{-# LINE 477 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "attachment" VkAttachmentReference = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (0)
{-# LINE 485 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "attachment" VkAttachmentReference where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 492 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 496 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "attachment" VkAttachmentReference where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 502 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "layout" VkAttachmentReference where
        type FieldType "layout" VkAttachmentReference = VkImageLayout
        type FieldOptional "layout" VkAttachmentReference = 'False -- ' closing tick for hsc2hs
        type FieldOffset "layout" VkAttachmentReference =
             (4)
{-# LINE 509 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "layout" VkAttachmentReference = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (4)
{-# LINE 516 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "layout" VkAttachmentReference where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (4))
{-# LINE 523 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (4)
{-# LINE 527 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "layout" VkAttachmentReference where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (4)
{-# LINE 533 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance Show VkAttachmentReference where
        showsPrec d x
          = showString "VkAttachmentReference {" .
              showString "attachment = " .
                showsPrec d (getField @"attachment" x) .
                  showString ", " .
                    showString "layout = " .
                      showsPrec d (getField @"layout" x) . showChar '}'

-- | > 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>
data VkAttachmentSampleLocationsEXT = VkAttachmentSampleLocationsEXT# Addr#
                                                                      ByteArray#

instance Eq VkAttachmentSampleLocationsEXT where
        (VkAttachmentSampleLocationsEXT# a _) ==
          x@(VkAttachmentSampleLocationsEXT# b _)
          = EQ == cmpBytes# (sizeOf x) a b

        {-# INLINE (==) #-}

instance Ord VkAttachmentSampleLocationsEXT where
        (VkAttachmentSampleLocationsEXT# a _) `compare`
          x@(VkAttachmentSampleLocationsEXT# b _) = cmpBytes# (sizeOf x) a b

        {-# INLINE compare #-}

instance Storable VkAttachmentSampleLocationsEXT where
        sizeOf ~_ = (48)
{-# LINE 567 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment ~_
          = (8)
{-# LINE 571 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE alignment #-}
        peek = peekVkData#

        {-# INLINE peek #-}
        poke = pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkAttachmentSampleLocationsEXT where
        unsafeAddr (VkAttachmentSampleLocationsEXT# a _) = a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray (VkAttachmentSampleLocationsEXT# _ b) = b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset off b
          = VkAttachmentSampleLocationsEXT#
              (plusAddr# (byteArrayContents# b) off)
              b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkAttachmentSampleLocationsEXT where
        type StructFields VkAttachmentSampleLocationsEXT =
             '["attachmentIndex", "sampleLocationsInfo"] -- ' closing tick for hsc2hs
        type CUnionType VkAttachmentSampleLocationsEXT = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkAttachmentSampleLocationsEXT = 'False -- ' closing tick for hsc2hs
        type StructExtends VkAttachmentSampleLocationsEXT = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "attachmentIndex" VkAttachmentSampleLocationsEXT where
        type FieldType "attachmentIndex" VkAttachmentSampleLocationsEXT =
             Word32
        type FieldOptional "attachmentIndex" VkAttachmentSampleLocationsEXT
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "attachmentIndex" VkAttachmentSampleLocationsEXT =
             (0)
{-# LINE 609 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "attachmentIndex" VkAttachmentSampleLocationsEXT
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (0)
{-# LINE 618 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "attachmentIndex" VkAttachmentSampleLocationsEXT where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 625 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (0)
{-# LINE 629 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "attachmentIndex" VkAttachmentSampleLocationsEXT
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 636 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "sampleLocationsInfo" VkAttachmentSampleLocationsEXT where
        type FieldType "sampleLocationsInfo" VkAttachmentSampleLocationsEXT
             = VkSampleLocationsInfoEXT
        type FieldOptional "sampleLocationsInfo"
               VkAttachmentSampleLocationsEXT
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "sampleLocationsInfo"
               VkAttachmentSampleLocationsEXT
             =
             (8)
{-# LINE 648 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
        type FieldIsArray "sampleLocationsInfo"
               VkAttachmentSampleLocationsEXT
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (8)
{-# LINE 658 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "sampleLocationsInfo" VkAttachmentSampleLocationsEXT
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 666 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (8)
{-# LINE 670 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "sampleLocationsInfo" VkAttachmentSampleLocationsEXT
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 677 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}

instance Show VkAttachmentSampleLocationsEXT where
        showsPrec d x
          = showString "VkAttachmentSampleLocationsEXT {" .
              showString "attachmentIndex = " .
                showsPrec d (getField @"attachmentIndex" x) .
                  showString ", " .
                    showString "sampleLocationsInfo = " .
                      showsPrec d (getField @"sampleLocationsInfo" x) . showChar '}'