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

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

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.FormatProperties
       (VkFormatProperties(..), VkFormatProperties2(..),
        VkFormatProperties2KHR)
       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.Format        (VkFormatFeatureFlags)
import           Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

-- | > typedef struct VkFormatProperties {
--   >     VkFormatFeatureFlags   linearTilingFeatures;
--   >     VkFormatFeatureFlags   optimalTilingFeatures;
--   >     VkFormatFeatureFlags   bufferFeatures;
--   > } VkFormatProperties;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkFormatProperties VkFormatProperties registry at www.khronos.org>
data VkFormatProperties = VkFormatProperties# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkFormatProperties where
        type StructFields VkFormatProperties =
             '["linearTilingFeatures", "optimalTilingFeatures", -- ' closing tick for hsc2hs
               "bufferFeatures"]
        type CUnionType VkFormatProperties = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkFormatProperties = 'True -- ' closing tick for hsc2hs
        type StructExtends VkFormatProperties = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-}
         HasField "linearTilingFeatures" VkFormatProperties where
        type FieldType "linearTilingFeatures" VkFormatProperties =
             VkFormatFeatureFlags
        type FieldOptional "linearTilingFeatures" VkFormatProperties =
             'True -- ' closing tick for hsc2hs
        type FieldOffset "linearTilingFeatures" VkFormatProperties =
             (0)
{-# LINE 87 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
        type FieldIsArray "linearTilingFeatures" VkFormatProperties =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

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

instance {-# OVERLAPPING #-}
         CanReadField "linearTilingFeatures" VkFormatProperties where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (0))
{-# LINE 103 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "linearTilingFeatures" VkFormatProperties where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (0)
{-# LINE 113 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "optimalTilingFeatures" VkFormatProperties where
        type FieldType "optimalTilingFeatures" VkFormatProperties =
             VkFormatFeatureFlags
        type FieldOptional "optimalTilingFeatures" VkFormatProperties =
             'True -- ' closing tick for hsc2hs
        type FieldOffset "optimalTilingFeatures" VkFormatProperties =
             (4)
{-# LINE 122 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
        type FieldIsArray "optimalTilingFeatures" VkFormatProperties =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

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

instance {-# OVERLAPPING #-}
         CanReadField "optimalTilingFeatures" VkFormatProperties where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (4))
{-# LINE 138 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "optimalTilingFeatures" VkFormatProperties where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (4)
{-# LINE 148 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "bufferFeatures" VkFormatProperties where
        type FieldType "bufferFeatures" VkFormatProperties =
             VkFormatFeatureFlags
        type FieldOptional "bufferFeatures" VkFormatProperties = 'True -- ' closing tick for hsc2hs
        type FieldOffset "bufferFeatures" VkFormatProperties =
             (8)
{-# LINE 156 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
        type FieldIsArray "bufferFeatures" VkFormatProperties = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

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

instance {-# OVERLAPPING #-}
         CanReadField "bufferFeatures" VkFormatProperties where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (8))
{-# LINE 171 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "bufferFeatures" VkFormatProperties where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (8)
{-# LINE 181 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}

instance Show VkFormatProperties where
        showsPrec d x
          = showString "VkFormatProperties {" .
              showString "linearTilingFeatures = " .
                showsPrec d (getField @"linearTilingFeatures" x) .
                  showString ", " .
                    showString "optimalTilingFeatures = " .
                      showsPrec d (getField @"optimalTilingFeatures" x) .
                        showString ", " .
                          showString "bufferFeatures = " .
                            showsPrec d (getField @"bufferFeatures" x) . showChar '}'

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkFormatProperties2 where
        sizeOf ~_ = (32)
{-# LINE 217 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "formatProperties" VkFormatProperties2 where
        type FieldType "formatProperties" VkFormatProperties2 =
             VkFormatProperties
        type FieldOptional "formatProperties" VkFormatProperties2 = 'False -- ' closing tick for hsc2hs
        type FieldOffset "formatProperties" VkFormatProperties2 =
             (16)
{-# LINE 317 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
        type FieldIsArray "formatProperties" VkFormatProperties2 = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "formatProperties" VkFormatProperties2 where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 332 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "formatProperties" VkFormatProperties2 where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 342 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}

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

-- | Alias for `VkFormatProperties2`
type VkFormatProperties2KHR = VkFormatProperties2