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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkTextureLODGatherFormatPropertiesAMD
-> IO (FieldType "sType" VkTextureLODGatherFormatPropertiesAMD)
readField Ptr VkTextureLODGatherFormatPropertiesAMD
p
          = Ptr VkTextureLODGatherFormatPropertiesAMD
-> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkTextureLODGatherFormatPropertiesAMD
p (Int
0)
{-# LINE 114 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkTextureLODGatherFormatPropertiesAMD
-> IO (FieldType "pNext" VkTextureLODGatherFormatPropertiesAMD)
readField Ptr VkTextureLODGatherFormatPropertiesAMD
p
          = Ptr VkTextureLODGatherFormatPropertiesAMD -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkTextureLODGatherFormatPropertiesAMD
p (Int
8)
{-# LINE 149 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

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

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

instance {-# OVERLAPPING #-}
         CanReadField "supportsTextureGatherLODBiasAMD"
           VkTextureLODGatherFormatPropertiesAMD
         where
        {-# NOINLINE getField #-}
        getField :: VkTextureLODGatherFormatPropertiesAMD
-> FieldType
     "supportsTextureGatherLODBiasAMD"
     VkTextureLODGatherFormatPropertiesAMD
getField VkTextureLODGatherFormatPropertiesAMD
x
          = IO VkBool32 -> VkBool32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkTextureLODGatherFormatPropertiesAMD -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkTextureLODGatherFormatPropertiesAMD
-> Ptr VkTextureLODGatherFormatPropertiesAMD
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkTextureLODGatherFormatPropertiesAMD
x) (Int
16))
{-# LINE 189 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkTextureLODGatherFormatPropertiesAMD
-> IO
     (FieldType
        "supportsTextureGatherLODBiasAMD"
        VkTextureLODGatherFormatPropertiesAMD)
readField Ptr VkTextureLODGatherFormatPropertiesAMD
p
          = Ptr VkTextureLODGatherFormatPropertiesAMD -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkTextureLODGatherFormatPropertiesAMD
p (Int
16)
{-# LINE 193 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "supportsTextureGatherLODBiasAMD"
           VkTextureLODGatherFormatPropertiesAMD
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkTextureLODGatherFormatPropertiesAMD
-> FieldType
     "supportsTextureGatherLODBiasAMD"
     VkTextureLODGatherFormatPropertiesAMD
-> IO ()
writeField Ptr VkTextureLODGatherFormatPropertiesAMD
p
          = Ptr VkTextureLODGatherFormatPropertiesAMD
-> Int -> VkBool32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkTextureLODGatherFormatPropertiesAMD
p (Int
16)
{-# LINE 201 "src-gen/Graphics/Vulkan/Types/Struct/TextureLODGatherFormatPropertiesAMD.hsc" #-}

instance Show VkTextureLODGatherFormatPropertiesAMD where
        showsPrec :: Int -> VkTextureLODGatherFormatPropertiesAMD -> ShowS
showsPrec Int
d VkTextureLODGatherFormatPropertiesAMD
x
          = String -> ShowS
showString String
"VkTextureLODGatherFormatPropertiesAMD {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"sType = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkStructureType -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkTextureLODGatherFormatPropertiesAMD
-> FieldType "sType" VkTextureLODGatherFormatPropertiesAMD
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkTextureLODGatherFormatPropertiesAMD
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
"pNext = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> Ptr Void -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkTextureLODGatherFormatPropertiesAMD
-> FieldType "pNext" VkTextureLODGatherFormatPropertiesAMD
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkTextureLODGatherFormatPropertiesAMD
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
"supportsTextureGatherLODBiasAMD = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkBool32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkTextureLODGatherFormatPropertiesAMD
-> FieldType
     "supportsTextureGatherLODBiasAMD"
     VkTextureLODGatherFormatPropertiesAMD
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"supportsTextureGatherLODBiasAMD" VkTextureLODGatherFormatPropertiesAMD
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                              Char -> ShowS
showChar Char
'}'