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

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

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.TextureLODGatherFormatPropertiesAMD
       (VkTextureLODGatherFormatPropertiesAMD(..)) 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.BaseTypes          (VkBool32)
import           Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import           Graphics.Vulkan.Types.Struct.Image       (VkImageFormatProperties2)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

-- | > typedef struct VkTextureLODGatherFormatPropertiesAMD {
--   >     VkStructureType sType;
--   >     void*                            pNext;
--   >     VkBool32                         supportsTextureGatherLODBiasAMD;
--   > } VkTextureLODGatherFormatPropertiesAMD;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkTextureLODGatherFormatPropertiesAMD VkTextureLODGatherFormatPropertiesAMD registry at www.khronos.org>
data VkTextureLODGatherFormatPropertiesAMD = VkTextureLODGatherFormatPropertiesAMD# Addr#
                                                                                    ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkTextureLODGatherFormatPropertiesAMD where
        sizeOf ~_
          = (24)
{-# LINE 50 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkTextureLODGatherFormatPropertiesAMD where
        type StructFields VkTextureLODGatherFormatPropertiesAMD =
             '["sType", "pNext", "supportsTextureGatherLODBiasAMD"] -- ' closing tick for hsc2hs
        type CUnionType VkTextureLODGatherFormatPropertiesAMD = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkTextureLODGatherFormatPropertiesAMD = 'True -- ' closing tick for hsc2hs
        type StructExtends VkTextureLODGatherFormatPropertiesAMD =
             '[VkImageFormatProperties2] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "sType" VkTextureLODGatherFormatPropertiesAMD where
        type FieldType "sType" VkTextureLODGatherFormatPropertiesAMD =
             VkStructureType
        type FieldOptional "sType" VkTextureLODGatherFormatPropertiesAMD =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "sType" VkTextureLODGatherFormatPropertiesAMD =
             (0)
{-# LINE 94 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}
        type FieldIsArray "sType" VkTextureLODGatherFormatPropertiesAMD =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "sType" VkTextureLODGatherFormatPropertiesAMD where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 110 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkTextureLODGatherFormatPropertiesAMD where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 120 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pNext" VkTextureLODGatherFormatPropertiesAMD where
        type FieldType "pNext" VkTextureLODGatherFormatPropertiesAMD =
             Ptr Void
        type FieldOptional "pNext" VkTextureLODGatherFormatPropertiesAMD =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "pNext" VkTextureLODGatherFormatPropertiesAMD =
             (8)
{-# LINE 129 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}
        type FieldIsArray "pNext" VkTextureLODGatherFormatPropertiesAMD =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "pNext" VkTextureLODGatherFormatPropertiesAMD where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 145 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkTextureLODGatherFormatPropertiesAMD where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 155 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "supportsTextureGatherLODBiasAMD"
           VkTextureLODGatherFormatPropertiesAMD
         where
        type FieldType "supportsTextureGatherLODBiasAMD"
               VkTextureLODGatherFormatPropertiesAMD
             = VkBool32
        type FieldOptional "supportsTextureGatherLODBiasAMD"
               VkTextureLODGatherFormatPropertiesAMD
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "supportsTextureGatherLODBiasAMD"
               VkTextureLODGatherFormatPropertiesAMD
             =
             (16)
{-# LINE 170 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}
        type FieldIsArray "supportsTextureGatherLODBiasAMD"
               VkTextureLODGatherFormatPropertiesAMD
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "supportsTextureGatherLODBiasAMD"
           VkTextureLODGatherFormatPropertiesAMD
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 189 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "supportsTextureGatherLODBiasAMD"
           VkTextureLODGatherFormatPropertiesAMD
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 201 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

instance Show VkTextureLODGatherFormatPropertiesAMD where
        showsPrec d x
          = showString "VkTextureLODGatherFormatPropertiesAMD {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "supportsTextureGatherLODBiasAMD = " .
                            showsPrec d (getField @"supportsTextureGatherLODBiasAMD" x) .
                              showChar '}'