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

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

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.InputAttachmentAspectReference
       (VkInputAttachmentAspectReference(..),
        VkInputAttachmentAspectReferenceKHR)
       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.Image (VkImageAspectFlags)
import           System.IO.Unsafe                 (unsafeDupablePerformIO)

-- | > typedef struct VkInputAttachmentAspectReference {
--   >     uint32_t                        subpass;
--   >     uint32_t                        inputAttachmentIndex;
--   >     VkImageAspectFlags              aspectMask;
--   > } VkInputAttachmentAspectReference;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkInputAttachmentAspectReference VkInputAttachmentAspectReference registry at www.khronos.org>
data VkInputAttachmentAspectReference = VkInputAttachmentAspectReference# Addr#
                                                                          ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkInputAttachmentAspectReference where
        sizeOf ~_ = (12)
{-# LINE 49 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkInputAttachmentAspectReference where
        type StructFields VkInputAttachmentAspectReference =
             '["subpass", "inputAttachmentIndex", "aspectMask"] -- ' closing tick for hsc2hs
        type CUnionType VkInputAttachmentAspectReference = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkInputAttachmentAspectReference = 'False -- ' closing tick for hsc2hs
        type StructExtends VkInputAttachmentAspectReference = '[] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "subpass" VkInputAttachmentAspectReference where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 106 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "subpass" VkInputAttachmentAspectReference where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "inputAttachmentIndex" VkInputAttachmentAspectReference
         where
        type FieldType "inputAttachmentIndex"
               VkInputAttachmentAspectReference
             = Word32
        type FieldOptional "inputAttachmentIndex"
               VkInputAttachmentAspectReference
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "inputAttachmentIndex"
               VkInputAttachmentAspectReference
             =
             (4)
{-# LINE 130 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}
        type FieldIsArray "inputAttachmentIndex"
               VkInputAttachmentAspectReference
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "inputAttachmentIndex"
           VkInputAttachmentAspectReference
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (4))
{-# LINE 149 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "inputAttachmentIndex"
           VkInputAttachmentAspectReference
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (4)
{-# LINE 161 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "aspectMask" VkInputAttachmentAspectReference where
        type FieldType "aspectMask" VkInputAttachmentAspectReference =
             VkImageAspectFlags
        type FieldOptional "aspectMask" VkInputAttachmentAspectReference =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "aspectMask" VkInputAttachmentAspectReference =
             (8)
{-# LINE 170 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}
        type FieldIsArray "aspectMask" VkInputAttachmentAspectReference =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "aspectMask" VkInputAttachmentAspectReference where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 186 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "aspectMask" VkInputAttachmentAspectReference where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 196 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

instance Show VkInputAttachmentAspectReference where
        showsPrec d x
          = showString "VkInputAttachmentAspectReference {" .
              showString "subpass = " .
                showsPrec d (getField @"subpass" x) .
                  showString ", " .
                    showString "inputAttachmentIndex = " .
                      showsPrec d (getField @"inputAttachmentIndex" x) .
                        showString ", " .
                          showString "aspectMask = " .
                            showsPrec d (getField @"aspectMask" x) . showChar '}'

-- | Alias for `VkInputAttachmentAspectReference`
type VkInputAttachmentAspectReferenceKHR =
     VkInputAttachmentAspectReference