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

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

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Import
       (VkImportFenceFdInfoKHR(..), VkImportMemoryFdInfoKHR(..),
        VkImportMemoryHostPointerInfoEXT(..),
        VkImportSemaphoreFdInfoKHR(..))
       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.External            (VkExternalFenceHandleTypeFlagBits,
                                                                 VkExternalMemoryHandleTypeFlagBits,
                                                                 VkExternalSemaphoreHandleTypeFlagBits)
import           Graphics.Vulkan.Types.Enum.Fence               (VkFenceImportFlags)
import           Graphics.Vulkan.Types.Enum.SemaphoreImportFlag (VkSemaphoreImportFlags)
import           Graphics.Vulkan.Types.Enum.StructureType       (VkStructureType)
import           Graphics.Vulkan.Types.Handles                  (VkFence,
                                                                 VkSemaphore)
import           Graphics.Vulkan.Types.Struct.Memory            (VkMemoryAllocateInfo)
import           System.IO.Unsafe                               (unsafeDupablePerformIO)

-- | > typedef struct VkImportFenceFdInfoKHR {
--   >     VkStructureType sType;
--   >     const void*                            pNext;
--   >     VkFence              fence;
--   >     VkFenceImportFlags  flags;
--   >     VkExternalFenceHandleTypeFlagBits   handleType;
--   >     int                                    fd;
--   > } VkImportFenceFdInfoKHR;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkImportFenceFdInfoKHR VkImportFenceFdInfoKHR registry at www.khronos.org>
data VkImportFenceFdInfoKHR = VkImportFenceFdInfoKHR# Addr#
                                                      ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkImportFenceFdInfoKHR where
        sizeOf ~_ = (40)
{-# LINE 60 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkImportFenceFdInfoKHR where
        type StructFields VkImportFenceFdInfoKHR =
             '["sType", "pNext", "fence", "flags", "handleType", "fd"] -- ' closing tick for hsc2hs
        type CUnionType VkImportFenceFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkImportFenceFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type StructExtends VkImportFenceFdInfoKHR = '[] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "fence" VkImportFenceFdInfoKHR where
        type FieldType "fence" VkImportFenceFdInfoKHR = VkFence
        type FieldOptional "fence" VkImportFenceFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "fence" VkImportFenceFdInfoKHR =
             (16)
{-# LINE 159 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "fence" VkImportFenceFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "fence" VkImportFenceFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 173 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "fence" VkImportFenceFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 183 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "flags" VkImportFenceFdInfoKHR where
        type FieldType "flags" VkImportFenceFdInfoKHR = VkFenceImportFlags
        type FieldOptional "flags" VkImportFenceFdInfoKHR = 'True -- ' closing tick for hsc2hs
        type FieldOffset "flags" VkImportFenceFdInfoKHR =
             (24)
{-# LINE 190 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "flags" VkImportFenceFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

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

instance {-# OVERLAPPING #-}
         CanReadField "flags" VkImportFenceFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (24))
{-# LINE 204 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "flags" VkImportFenceFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (24)
{-# LINE 214 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "handleType" VkImportFenceFdInfoKHR where
        type FieldType "handleType" VkImportFenceFdInfoKHR =
             VkExternalFenceHandleTypeFlagBits
        type FieldOptional "handleType" VkImportFenceFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "handleType" VkImportFenceFdInfoKHR =
             (28)
{-# LINE 222 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "handleType" VkImportFenceFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (28)
{-# LINE 230 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "handleType" VkImportFenceFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (28))
{-# LINE 237 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (28)
{-# LINE 241 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "handleType" VkImportFenceFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (28)
{-# LINE 247 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-} HasField "fd" VkImportFenceFdInfoKHR
         where
        type FieldType "fd" VkImportFenceFdInfoKHR = CInt
        type FieldOptional "fd" VkImportFenceFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "fd" VkImportFenceFdInfoKHR =
             (32)
{-# LINE 254 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "fd" VkImportFenceFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "fd" VkImportFenceFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (32))
{-# LINE 268 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "fd" VkImportFenceFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (32)
{-# LINE 278 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance Show VkImportFenceFdInfoKHR where
        showsPrec d x
          = showString "VkImportFenceFdInfoKHR {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "fence = " .
                            showsPrec d (getField @"fence" x) .
                              showString ", " .
                                showString "flags = " .
                                  showsPrec d (getField @"flags" x) .
                                    showString ", " .
                                      showString "handleType = " .
                                        showsPrec d (getField @"handleType" x) .
                                          showString ", " .
                                            showString "fd = " .
                                              showsPrec d (getField @"fd" x) . showChar '}'

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkImportMemoryFdInfoKHR where
        type StructFields VkImportMemoryFdInfoKHR =
             '["sType", "pNext", "handleType", "fd"] -- ' closing tick for hsc2hs
        type CUnionType VkImportMemoryFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkImportMemoryFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type StructExtends VkImportMemoryFdInfoKHR =
             '[VkMemoryAllocateInfo] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "handleType" VkImportMemoryFdInfoKHR where
        type FieldType "handleType" VkImportMemoryFdInfoKHR =
             VkExternalMemoryHandleTypeFlagBits
        type FieldOptional "handleType" VkImportMemoryFdInfoKHR = 'True -- ' closing tick for hsc2hs
        type FieldOffset "handleType" VkImportMemoryFdInfoKHR =
             (16)
{-# LINE 426 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "handleType" VkImportMemoryFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

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

instance {-# OVERLAPPING #-}
         CanReadField "handleType" VkImportMemoryFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 441 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "handleType" VkImportMemoryFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 451 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-} HasField "fd" VkImportMemoryFdInfoKHR
         where
        type FieldType "fd" VkImportMemoryFdInfoKHR = CInt
        type FieldOptional "fd" VkImportMemoryFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "fd" VkImportMemoryFdInfoKHR =
             (20)
{-# LINE 458 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "fd" VkImportMemoryFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (20)
{-# LINE 465 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "fd" VkImportMemoryFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (20))
{-# LINE 472 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (20)
{-# LINE 476 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "fd" VkImportMemoryFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (20)
{-# LINE 482 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkImportMemoryHostPointerInfoEXT where
        type StructFields VkImportMemoryHostPointerInfoEXT =
             '["sType", "pNext", "handleType", "pHostPointer"] -- ' closing tick for hsc2hs
        type CUnionType VkImportMemoryHostPointerInfoEXT = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkImportMemoryHostPointerInfoEXT = 'False -- ' closing tick for hsc2hs
        type StructExtends VkImportMemoryHostPointerInfoEXT =
             '[VkMemoryAllocateInfo] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "handleType" VkImportMemoryHostPointerInfoEXT where
        type FieldType "handleType" VkImportMemoryHostPointerInfoEXT =
             VkExternalMemoryHandleTypeFlagBits
        type FieldOptional "handleType" VkImportMemoryHostPointerInfoEXT =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "handleType" VkImportMemoryHostPointerInfoEXT =
             (16)
{-# LINE 634 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "handleType" VkImportMemoryHostPointerInfoEXT =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "handleType" VkImportMemoryHostPointerInfoEXT where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 650 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "handleType" VkImportMemoryHostPointerInfoEXT where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 660 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "pHostPointer" VkImportMemoryHostPointerInfoEXT where
        type FieldType "pHostPointer" VkImportMemoryHostPointerInfoEXT =
             Ptr Void
        type FieldOptional "pHostPointer" VkImportMemoryHostPointerInfoEXT
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "pHostPointer" VkImportMemoryHostPointerInfoEXT =
             (24)
{-# LINE 669 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "pHostPointer" VkImportMemoryHostPointerInfoEXT =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "pHostPointer" VkImportMemoryHostPointerInfoEXT where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (24))
{-# LINE 685 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "pHostPointer" VkImportMemoryHostPointerInfoEXT where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (24)
{-# LINE 695 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

-- | > typedef struct VkImportSemaphoreFdInfoKHR {
--   >     VkStructureType sType;
--   >     const void*                      pNext;
--   >     VkSemaphore    semaphore;
--   >     VkSemaphoreImportFlags flags;
--   >     VkExternalSemaphoreHandleTypeFlagBits handleType;
--   >     int                              fd;
--   > } VkImportSemaphoreFdInfoKHR;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkImportSemaphoreFdInfoKHR VkImportSemaphoreFdInfoKHR registry at www.khronos.org>
data VkImportSemaphoreFdInfoKHR = VkImportSemaphoreFdInfoKHR# Addr#
                                                              ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkImportSemaphoreFdInfoKHR where
        sizeOf ~_ = (40)
{-# LINE 739 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkImportSemaphoreFdInfoKHR where
        type StructFields VkImportSemaphoreFdInfoKHR =
             '["sType", "pNext", "semaphore", "flags", "handleType", "fd"] -- ' closing tick for hsc2hs
        type CUnionType VkImportSemaphoreFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkImportSemaphoreFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type StructExtends VkImportSemaphoreFdInfoKHR = '[] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "semaphore" VkImportSemaphoreFdInfoKHR where
        type FieldType "semaphore" VkImportSemaphoreFdInfoKHR = VkSemaphore
        type FieldOptional "semaphore" VkImportSemaphoreFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "semaphore" VkImportSemaphoreFdInfoKHR =
             (16)
{-# LINE 842 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "semaphore" VkImportSemaphoreFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

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

instance {-# OVERLAPPING #-}
         CanReadField "semaphore" VkImportSemaphoreFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (16))
{-# LINE 857 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "semaphore" VkImportSemaphoreFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (16)
{-# LINE 867 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "flags" VkImportSemaphoreFdInfoKHR where
        type FieldType "flags" VkImportSemaphoreFdInfoKHR =
             VkSemaphoreImportFlags
        type FieldOptional "flags" VkImportSemaphoreFdInfoKHR = 'True -- ' closing tick for hsc2hs
        type FieldOffset "flags" VkImportSemaphoreFdInfoKHR =
             (24)
{-# LINE 875 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "flags" VkImportSemaphoreFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = True

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

instance {-# OVERLAPPING #-}
         CanReadField "flags" VkImportSemaphoreFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (24))
{-# LINE 890 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

instance {-# OVERLAPPING #-}
         CanWriteField "flags" VkImportSemaphoreFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (24)
{-# LINE 900 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "handleType" VkImportSemaphoreFdInfoKHR where
        type FieldType "handleType" VkImportSemaphoreFdInfoKHR =
             VkExternalSemaphoreHandleTypeFlagBits
        type FieldOptional "handleType" VkImportSemaphoreFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "handleType" VkImportSemaphoreFdInfoKHR =
             (28)
{-# LINE 908 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "handleType" VkImportSemaphoreFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset
          = (28)
{-# LINE 916 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "handleType" VkImportSemaphoreFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (28))
{-# LINE 923 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (28)
{-# LINE 927 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "handleType" VkImportSemaphoreFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (28)
{-# LINE 933 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "fd" VkImportSemaphoreFdInfoKHR where
        type FieldType "fd" VkImportSemaphoreFdInfoKHR = CInt
        type FieldOptional "fd" VkImportSemaphoreFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "fd" VkImportSemaphoreFdInfoKHR =
             (32)
{-# LINE 940 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}
        type FieldIsArray "fd" VkImportSemaphoreFdInfoKHR = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional = False

        {-# INLINE fieldOffset #-}
        fieldOffset = (32)
{-# LINE 947 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanReadField "fd" VkImportSemaphoreFdInfoKHR where
        {-# NOINLINE getField #-}
        getField x
          = unsafeDupablePerformIO
              (peekByteOff (unsafePtr x) (32))
{-# LINE 954 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField p
          = peekByteOff p (32)
{-# LINE 958 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "fd" VkImportSemaphoreFdInfoKHR where
        {-# INLINE writeField #-}
        writeField p
          = pokeByteOff p (32)
{-# LINE 964 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance Show VkImportSemaphoreFdInfoKHR where
        showsPrec d x
          = showString "VkImportSemaphoreFdInfoKHR {" .
              showString "sType = " .
                showsPrec d (getField @"sType" x) .
                  showString ", " .
                    showString "pNext = " .
                      showsPrec d (getField @"pNext" x) .
                        showString ", " .
                          showString "semaphore = " .
                            showsPrec d (getField @"semaphore" x) .
                              showString ", " .
                                showString "flags = " .
                                  showsPrec d (getField @"flags" x) .
                                    showString ", " .
                                      showString "handleType = " .
                                        showsPrec d (getField @"handleType" x) .
                                          showString ", " .
                                            showString "fd = " .
                                              showsPrec d (getField @"fd" x) . showChar '}'