{-# LINE 1 "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# Addr#
a ByteArray#
_) == :: VkInputAttachmentAspectReference
-> VkInputAttachmentAspectReference -> Bool
==
          x :: VkInputAttachmentAspectReference
x@(VkInputAttachmentAspectReference# Addr#
b ByteArray#
_)
          = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkInputAttachmentAspectReference -> Int
forall a. Storable a => a -> Int
sizeOf VkInputAttachmentAspectReference
x) Addr#
a Addr#
b

        {-# INLINE (==) #-}

instance Ord VkInputAttachmentAspectReference where
        (VkInputAttachmentAspectReference# Addr#
a ByteArray#
_) compare :: VkInputAttachmentAspectReference
-> VkInputAttachmentAspectReference -> Ordering
`compare`
          x :: VkInputAttachmentAspectReference
x@(VkInputAttachmentAspectReference# Addr#
b ByteArray#
_)
          = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkInputAttachmentAspectReference -> Int
forall a. Storable a => a -> Int
sizeOf VkInputAttachmentAspectReference
x) Addr#
a Addr#
b

        {-# INLINE compare #-}

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

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

        {-# INLINE alignment #-}
        peek :: Ptr VkInputAttachmentAspectReference
-> IO VkInputAttachmentAspectReference
peek = Ptr VkInputAttachmentAspectReference
-> IO VkInputAttachmentAspectReference
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#

        {-# INLINE peek #-}
        poke :: Ptr VkInputAttachmentAspectReference
-> VkInputAttachmentAspectReference -> IO ()
poke = Ptr VkInputAttachmentAspectReference
-> VkInputAttachmentAspectReference -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#

        {-# INLINE poke #-}

instance VulkanMarshalPrim VkInputAttachmentAspectReference where
        unsafeAddr :: VkInputAttachmentAspectReference -> Addr#
unsafeAddr (VkInputAttachmentAspectReference# Addr#
a ByteArray#
_) = Addr#
a

        {-# INLINE unsafeAddr #-}
        unsafeByteArray :: VkInputAttachmentAspectReference -> ByteArray#
unsafeByteArray (VkInputAttachmentAspectReference# Addr#
_ ByteArray#
b) = ByteArray#
b

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkInputAttachmentAspectReference
unsafeFromByteArrayOffset Int#
off ByteArray#
b
          = Addr# -> ByteArray# -> VkInputAttachmentAspectReference
VkInputAttachmentAspectReference#
              (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
              ByteArray#
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 :: Bool
fieldOptional = Bool
False

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

instance {-# OVERLAPPING #-}
         CanReadField "subpass" VkInputAttachmentAspectReference where
        {-# NOINLINE getField #-}
        getField :: VkInputAttachmentAspectReference
-> FieldType "subpass" VkInputAttachmentAspectReference
getField VkInputAttachmentAspectReference
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkInputAttachmentAspectReference -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInputAttachmentAspectReference
-> Ptr VkInputAttachmentAspectReference
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInputAttachmentAspectReference
x) (Int
0))
{-# LINE 106 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkInputAttachmentAspectReference
-> IO (FieldType "subpass" VkInputAttachmentAspectReference)
readField Ptr VkInputAttachmentAspectReference
p
          = Ptr VkInputAttachmentAspectReference -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInputAttachmentAspectReference
p (Int
0)
{-# LINE 110 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "subpass" VkInputAttachmentAspectReference where
        {-# INLINE writeField #-}
        writeField :: Ptr VkInputAttachmentAspectReference
-> FieldType "subpass" VkInputAttachmentAspectReference -> IO ()
writeField Ptr VkInputAttachmentAspectReference
p
          = Ptr VkInputAttachmentAspectReference -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInputAttachmentAspectReference
p (Int
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 :: Bool
fieldOptional = Bool
False

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

instance {-# OVERLAPPING #-}
         CanReadField "inputAttachmentIndex"
           VkInputAttachmentAspectReference
         where
        {-# NOINLINE getField #-}
        getField :: VkInputAttachmentAspectReference
-> FieldType
     "inputAttachmentIndex" VkInputAttachmentAspectReference
getField VkInputAttachmentAspectReference
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkInputAttachmentAspectReference -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInputAttachmentAspectReference
-> Ptr VkInputAttachmentAspectReference
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInputAttachmentAspectReference
x) (Int
4))
{-# LINE 149 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkInputAttachmentAspectReference
-> IO
     (FieldType "inputAttachmentIndex" VkInputAttachmentAspectReference)
readField Ptr VkInputAttachmentAspectReference
p
          = Ptr VkInputAttachmentAspectReference -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInputAttachmentAspectReference
p (Int
4)
{-# LINE 153 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "inputAttachmentIndex"
           VkInputAttachmentAspectReference
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkInputAttachmentAspectReference
-> FieldType
     "inputAttachmentIndex" VkInputAttachmentAspectReference
-> IO ()
writeField Ptr VkInputAttachmentAspectReference
p
          = Ptr VkInputAttachmentAspectReference -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInputAttachmentAspectReference
p (Int
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 :: Bool
fieldOptional = Bool
False

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

instance {-# OVERLAPPING #-}
         CanReadField "aspectMask" VkInputAttachmentAspectReference where
        {-# NOINLINE getField #-}
        getField :: VkInputAttachmentAspectReference
-> FieldType "aspectMask" VkInputAttachmentAspectReference
getField VkInputAttachmentAspectReference
x
          = IO VkImageAspectFlags -> VkImageAspectFlags
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkInputAttachmentAspectReference
-> Int -> IO VkImageAspectFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInputAttachmentAspectReference
-> Ptr VkInputAttachmentAspectReference
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInputAttachmentAspectReference
x) (Int
8))
{-# LINE 186 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkInputAttachmentAspectReference
-> IO (FieldType "aspectMask" VkInputAttachmentAspectReference)
readField Ptr VkInputAttachmentAspectReference
p
          = Ptr VkInputAttachmentAspectReference
-> Int -> IO VkImageAspectFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInputAttachmentAspectReference
p (Int
8)
{-# LINE 190 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "aspectMask" VkInputAttachmentAspectReference where
        {-# INLINE writeField #-}
        writeField :: Ptr VkInputAttachmentAspectReference
-> FieldType "aspectMask" VkInputAttachmentAspectReference -> IO ()
writeField Ptr VkInputAttachmentAspectReference
p
          = Ptr VkInputAttachmentAspectReference
-> Int -> VkImageAspectFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInputAttachmentAspectReference
p (Int
8)
{-# LINE 196 "src-gen/Graphics/Vulkan/Types/Struct/InputAttachmentAspectReference.hsc" #-}

instance Show VkInputAttachmentAspectReference where
        showsPrec :: Int -> VkInputAttachmentAspectReference -> ShowS
showsPrec Int
d VkInputAttachmentAspectReference
x
          = String -> ShowS
showString String
"VkInputAttachmentAspectReference {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"subpass = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkInputAttachmentAspectReference
-> FieldType "subpass" VkInputAttachmentAspectReference
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"subpass" VkInputAttachmentAspectReference
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                  String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                    String -> ShowS
showString String
"inputAttachmentIndex = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkInputAttachmentAspectReference
-> FieldType
     "inputAttachmentIndex" VkInputAttachmentAspectReference
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"inputAttachmentIndex" VkInputAttachmentAspectReference
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                        String -> ShowS
showString String
", " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                          String -> ShowS
showString String
"aspectMask = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkImageAspectFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkInputAttachmentAspectReference
-> FieldType "aspectMask" VkInputAttachmentAspectReference
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"aspectMask" VkInputAttachmentAspectReference
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'

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