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

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

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.DedicatedAllocation
       (VkDedicatedAllocationBufferCreateInfoNV(..),
        VkDedicatedAllocationImageCreateInfoNV(..),
        VkDedicatedAllocationMemoryAllocateInfoNV(..))
       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.Handles            (VkBuffer, VkImage)
import           Graphics.Vulkan.Types.Struct.Buffer      (VkBufferCreateInfo)
import           Graphics.Vulkan.Types.Struct.Image       (VkImageCreateInfo)
import           Graphics.Vulkan.Types.Struct.Memory      (VkMemoryAllocateInfo)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkDedicatedAllocationBufferCreateInfoNV
         where
        type StructFields VkDedicatedAllocationBufferCreateInfoNV =
             '["sType", "pNext", "dedicatedAllocation"] -- ' closing tick for hsc2hs
        type CUnionType VkDedicatedAllocationBufferCreateInfoNV = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkDedicatedAllocationBufferCreateInfoNV = 'False -- ' closing tick for hsc2hs
        type StructExtends VkDedicatedAllocationBufferCreateInfoNV =
             '[VkBufferCreateInfo] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "dedicatedAllocation"
           VkDedicatedAllocationBufferCreateInfoNV
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 196 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "dedicatedAllocation"
           VkDedicatedAllocationBufferCreateInfoNV
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 208 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

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

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkDedicatedAllocationImageCreateInfoNV where
        type StructFields VkDedicatedAllocationImageCreateInfoNV =
             '["sType", "pNext", "dedicatedAllocation"] -- ' closing tick for hsc2hs
        type CUnionType VkDedicatedAllocationImageCreateInfoNV = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkDedicatedAllocationImageCreateInfoNV = 'False -- ' closing tick for hsc2hs
        type StructExtends VkDedicatedAllocationImageCreateInfoNV =
             '[VkImageCreateInfo] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "dedicatedAllocation"
           VkDedicatedAllocationImageCreateInfoNV
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 387 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "dedicatedAllocation"
           VkDedicatedAllocationImageCreateInfoNV
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 399 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

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

-- | > typedef struct VkDedicatedAllocationMemoryAllocateInfoNV {
--   >     VkStructureType sType;
--   >     const void*                      pNext;
--   >     VkImage          image;
--   >     VkBuffer         buffer;
--   > } VkDedicatedAllocationMemoryAllocateInfoNV;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkDedicatedAllocationMemoryAllocateInfoNV VkDedicatedAllocationMemoryAllocateInfoNV registry at www.khronos.org>
data VkDedicatedAllocationMemoryAllocateInfoNV = VkDedicatedAllocationMemoryAllocateInfoNV# Addr#
                                                                                            ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkDedicatedAllocationMemoryAllocateInfoNV
         where
        type StructFields VkDedicatedAllocationMemoryAllocateInfoNV =
             '["sType", "pNext", "image", "buffer"] -- ' closing tick for hsc2hs
        type CUnionType VkDedicatedAllocationMemoryAllocateInfoNV = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkDedicatedAllocationMemoryAllocateInfoNV =
             'False -- ' closing tick for hsc2hs
        type StructExtends VkDedicatedAllocationMemoryAllocateInfoNV =
             '[VkMemoryAllocateInfo] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "image" VkDedicatedAllocationMemoryAllocateInfoNV where
        type FieldType "image" VkDedicatedAllocationMemoryAllocateInfoNV =
             VkImage
        type FieldOptional "image"
               VkDedicatedAllocationMemoryAllocateInfoNV
             = 'True -- ' closing tick for hsc2hs
        type FieldOffset "image" VkDedicatedAllocationMemoryAllocateInfoNV
             =
             (16)
{-# LINE 568 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
        type FieldIsArray "image" VkDedicatedAllocationMemoryAllocateInfoNV
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

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

instance {-# OVERLAPPING #-}
         CanReadField "image" VkDedicatedAllocationMemoryAllocateInfoNV
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 585 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "image" VkDedicatedAllocationMemoryAllocateInfoNV
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 596 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "buffer" VkDedicatedAllocationMemoryAllocateInfoNV where
        type FieldType "buffer" VkDedicatedAllocationMemoryAllocateInfoNV =
             VkBuffer
        type FieldOptional "buffer"
               VkDedicatedAllocationMemoryAllocateInfoNV
             = 'True -- ' closing tick for hsc2hs
        type FieldOffset "buffer" VkDedicatedAllocationMemoryAllocateInfoNV
             =
             (24)
{-# LINE 607 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
        type FieldIsArray "buffer"
               VkDedicatedAllocationMemoryAllocateInfoNV
             = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (24)
{-# LINE 617 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "buffer" VkDedicatedAllocationMemoryAllocateInfoNV
         where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (24))
{-# LINE 625 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (24)
{-# LINE 629 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "buffer" VkDedicatedAllocationMemoryAllocateInfoNV
         where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (24)
{-# LINE 636 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}

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