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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkImportFenceFdInfoKHR
-> IO (FieldType "fence" VkImportFenceFdInfoKHR)
readField Ptr VkImportFenceFdInfoKHR
p
          = Ptr VkImportFenceFdInfoKHR -> Int -> IO VkFence
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportFenceFdInfoKHR
p (Int
16)
{-# LINE 177 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

instance {-# OVERLAPPING #-}
         CanReadField "flags" VkImportFenceFdInfoKHR where
        {-# NOINLINE getField #-}
        getField :: VkImportFenceFdInfoKHR -> FieldType "flags" VkImportFenceFdInfoKHR
getField VkImportFenceFdInfoKHR
x
          = IO VkFenceImportFlags -> VkFenceImportFlags
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkImportFenceFdInfoKHR -> Int -> IO VkFenceImportFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkImportFenceFdInfoKHR -> Ptr VkImportFenceFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkImportFenceFdInfoKHR
x) (Int
24))
{-# LINE 204 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkImportFenceFdInfoKHR
-> IO (FieldType "flags" VkImportFenceFdInfoKHR)
readField Ptr VkImportFenceFdInfoKHR
p
          = Ptr VkImportFenceFdInfoKHR -> Int -> IO VkFenceImportFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportFenceFdInfoKHR
p (Int
24)
{-# LINE 208 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

instance {-# OVERLAPPING #-}
         CanReadField "handleType" VkImportFenceFdInfoKHR where
        {-# NOINLINE getField #-}
        getField :: VkImportFenceFdInfoKHR
-> FieldType "handleType" VkImportFenceFdInfoKHR
getField VkImportFenceFdInfoKHR
x
          = IO VkExternalFenceHandleTypeFlagBits
-> VkExternalFenceHandleTypeFlagBits
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkImportFenceFdInfoKHR
-> Int -> IO VkExternalFenceHandleTypeFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkImportFenceFdInfoKHR -> Ptr VkImportFenceFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkImportFenceFdInfoKHR
x) (Int
28))
{-# LINE 237 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkImportFenceFdInfoKHR
-> IO (FieldType "handleType" VkImportFenceFdInfoKHR)
readField Ptr VkImportFenceFdInfoKHR
p
          = Ptr VkImportFenceFdInfoKHR
-> Int -> IO VkExternalFenceHandleTypeFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportFenceFdInfoKHR
p (Int
28)
{-# LINE 241 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

instance {-# OVERLAPPING #-}
         CanReadField "fd" VkImportFenceFdInfoKHR where
        {-# NOINLINE getField #-}
        getField :: VkImportFenceFdInfoKHR -> FieldType "fd" VkImportFenceFdInfoKHR
getField VkImportFenceFdInfoKHR
x
          = IO CInt -> CInt
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkImportFenceFdInfoKHR -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkImportFenceFdInfoKHR -> Ptr VkImportFenceFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkImportFenceFdInfoKHR
x) (Int
32))
{-# LINE 268 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkImportFenceFdInfoKHR
-> IO (FieldType "fd" VkImportFenceFdInfoKHR)
readField Ptr VkImportFenceFdInfoKHR
p
          = Ptr VkImportFenceFdInfoKHR -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportFenceFdInfoKHR
p (Int
32)
{-# LINE 272 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "fd" VkImportFenceFdInfoKHR where
        {-# INLINE writeField #-}
        writeField :: Ptr VkImportFenceFdInfoKHR
-> FieldType "fd" VkImportFenceFdInfoKHR -> IO ()
writeField Ptr VkImportFenceFdInfoKHR
p
          = Ptr VkImportFenceFdInfoKHR -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkImportFenceFdInfoKHR
p (Int
32)
{-# LINE 278 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance Show VkImportFenceFdInfoKHR where
        showsPrec :: Int -> VkImportFenceFdInfoKHR -> ShowS
showsPrec Int
d VkImportFenceFdInfoKHR
x
          = String -> ShowS
showString String
"VkImportFenceFdInfoKHR {" 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 (VkImportFenceFdInfoKHR -> FieldType "sType" VkImportFenceFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkImportFenceFdInfoKHR
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 (VkImportFenceFdInfoKHR -> FieldType "pNext" VkImportFenceFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkImportFenceFdInfoKHR
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
"fence = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkFence -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportFenceFdInfoKHR -> FieldType "fence" VkImportFenceFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"fence" VkImportFenceFdInfoKHR
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
"flags = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                  Int -> VkFenceImportFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportFenceFdInfoKHR -> FieldType "flags" VkImportFenceFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkImportFenceFdInfoKHR
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
"handleType = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                        Int -> VkExternalFenceHandleTypeFlagBits -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportFenceFdInfoKHR
-> FieldType "handleType" VkImportFenceFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"handleType" VkImportFenceFdInfoKHR
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
"fd = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                              Int -> CInt -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportFenceFdInfoKHR -> FieldType "fd" VkImportFenceFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"fd" VkImportFenceFdInfoKHR
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkImportMemoryFdInfoKHR
-> IO (FieldType "handleType" VkImportMemoryFdInfoKHR)
readField Ptr VkImportMemoryFdInfoKHR
p
          = Ptr VkImportMemoryFdInfoKHR
-> Int -> IO VkExternalMemoryHandleTypeFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportMemoryFdInfoKHR
p (Int
16)
{-# LINE 445 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

instance {-# OVERLAPPING #-}
         CanReadField "fd" VkImportMemoryFdInfoKHR where
        {-# NOINLINE getField #-}
        getField :: VkImportMemoryFdInfoKHR -> FieldType "fd" VkImportMemoryFdInfoKHR
getField VkImportMemoryFdInfoKHR
x
          = IO CInt -> CInt
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkImportMemoryFdInfoKHR -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkImportMemoryFdInfoKHR -> Ptr VkImportMemoryFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkImportMemoryFdInfoKHR
x) (Int
20))
{-# LINE 472 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkImportMemoryFdInfoKHR
-> IO (FieldType "fd" VkImportMemoryFdInfoKHR)
readField Ptr VkImportMemoryFdInfoKHR
p
          = Ptr VkImportMemoryFdInfoKHR -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportMemoryFdInfoKHR
p (Int
20)
{-# LINE 476 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "fd" VkImportMemoryFdInfoKHR where
        {-# INLINE writeField #-}
        writeField :: Ptr VkImportMemoryFdInfoKHR
-> FieldType "fd" VkImportMemoryFdInfoKHR -> IO ()
writeField Ptr VkImportMemoryFdInfoKHR
p
          = Ptr VkImportMemoryFdInfoKHR -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkImportMemoryFdInfoKHR
p (Int
20)
{-# LINE 482 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance Show VkImportMemoryFdInfoKHR where
        showsPrec :: Int -> VkImportMemoryFdInfoKHR -> ShowS
showsPrec Int
d VkImportMemoryFdInfoKHR
x
          = String -> ShowS
showString String
"VkImportMemoryFdInfoKHR {" 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 (VkImportMemoryFdInfoKHR
-> FieldType "sType" VkImportMemoryFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkImportMemoryFdInfoKHR
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 (VkImportMemoryFdInfoKHR
-> FieldType "pNext" VkImportMemoryFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkImportMemoryFdInfoKHR
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
"handleType = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkExternalMemoryHandleTypeFlagBits -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportMemoryFdInfoKHR
-> FieldType "handleType" VkImportMemoryFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"handleType" VkImportMemoryFdInfoKHR
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
"fd = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> CInt -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportMemoryFdInfoKHR -> FieldType "fd" VkImportMemoryFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"fd" VkImportMemoryFdInfoKHR
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkImportMemoryHostPointerInfoEXT
-> IO (FieldType "handleType" VkImportMemoryHostPointerInfoEXT)
readField Ptr VkImportMemoryHostPointerInfoEXT
p
          = Ptr VkImportMemoryHostPointerInfoEXT
-> Int -> IO VkExternalMemoryHandleTypeFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportMemoryHostPointerInfoEXT
p (Int
16)
{-# LINE 654 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkImportMemoryHostPointerInfoEXT
-> IO (FieldType "pHostPointer" VkImportMemoryHostPointerInfoEXT)
readField Ptr VkImportMemoryHostPointerInfoEXT
p
          = Ptr VkImportMemoryHostPointerInfoEXT -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportMemoryHostPointerInfoEXT
p (Int
24)
{-# LINE 689 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "pHostPointer" VkImportMemoryHostPointerInfoEXT where
        {-# INLINE writeField #-}
        writeField :: Ptr VkImportMemoryHostPointerInfoEXT
-> FieldType "pHostPointer" VkImportMemoryHostPointerInfoEXT
-> IO ()
writeField Ptr VkImportMemoryHostPointerInfoEXT
p
          = Ptr VkImportMemoryHostPointerInfoEXT -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkImportMemoryHostPointerInfoEXT
p (Int
24)
{-# LINE 695 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkImportSemaphoreFdInfoKHR
-> IO (FieldType "semaphore" VkImportSemaphoreFdInfoKHR)
readField Ptr VkImportSemaphoreFdInfoKHR
p
          = Ptr VkImportSemaphoreFdInfoKHR -> Int -> IO VkSemaphore
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportSemaphoreFdInfoKHR
p (Int
16)
{-# LINE 861 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

instance {-# OVERLAPPING #-}
         CanReadField "flags" VkImportSemaphoreFdInfoKHR where
        {-# NOINLINE getField #-}
        getField :: VkImportSemaphoreFdInfoKHR
-> FieldType "flags" VkImportSemaphoreFdInfoKHR
getField VkImportSemaphoreFdInfoKHR
x
          = IO VkSemaphoreImportFlags -> VkSemaphoreImportFlags
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkImportSemaphoreFdInfoKHR -> Int -> IO VkSemaphoreImportFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkImportSemaphoreFdInfoKHR -> Ptr VkImportSemaphoreFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkImportSemaphoreFdInfoKHR
x) (Int
24))
{-# LINE 890 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkImportSemaphoreFdInfoKHR
-> IO (FieldType "flags" VkImportSemaphoreFdInfoKHR)
readField Ptr VkImportSemaphoreFdInfoKHR
p
          = Ptr VkImportSemaphoreFdInfoKHR -> Int -> IO VkSemaphoreImportFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportSemaphoreFdInfoKHR
p (Int
24)
{-# LINE 894 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

instance {-# OVERLAPPING #-}
         CanReadField "handleType" VkImportSemaphoreFdInfoKHR where
        {-# NOINLINE getField #-}
        getField :: VkImportSemaphoreFdInfoKHR
-> FieldType "handleType" VkImportSemaphoreFdInfoKHR
getField VkImportSemaphoreFdInfoKHR
x
          = IO VkExternalSemaphoreHandleTypeFlagBits
-> VkExternalSemaphoreHandleTypeFlagBits
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkImportSemaphoreFdInfoKHR
-> Int -> IO VkExternalSemaphoreHandleTypeFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkImportSemaphoreFdInfoKHR -> Ptr VkImportSemaphoreFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkImportSemaphoreFdInfoKHR
x) (Int
28))
{-# LINE 923 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkImportSemaphoreFdInfoKHR
-> IO (FieldType "handleType" VkImportSemaphoreFdInfoKHR)
readField Ptr VkImportSemaphoreFdInfoKHR
p
          = Ptr VkImportSemaphoreFdInfoKHR
-> Int -> IO VkExternalSemaphoreHandleTypeFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportSemaphoreFdInfoKHR
p (Int
28)
{-# LINE 927 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

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

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

instance {-# OVERLAPPING #-}
         CanReadField "fd" VkImportSemaphoreFdInfoKHR where
        {-# NOINLINE getField #-}
        getField :: VkImportSemaphoreFdInfoKHR
-> FieldType "fd" VkImportSemaphoreFdInfoKHR
getField VkImportSemaphoreFdInfoKHR
x
          = IO CInt -> CInt
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkImportSemaphoreFdInfoKHR -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkImportSemaphoreFdInfoKHR -> Ptr VkImportSemaphoreFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkImportSemaphoreFdInfoKHR
x) (Int
32))
{-# LINE 954 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkImportSemaphoreFdInfoKHR
-> IO (FieldType "fd" VkImportSemaphoreFdInfoKHR)
readField Ptr VkImportSemaphoreFdInfoKHR
p
          = Ptr VkImportSemaphoreFdInfoKHR -> Int -> IO CInt
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkImportSemaphoreFdInfoKHR
p (Int
32)
{-# LINE 958 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "fd" VkImportSemaphoreFdInfoKHR where
        {-# INLINE writeField #-}
        writeField :: Ptr VkImportSemaphoreFdInfoKHR
-> FieldType "fd" VkImportSemaphoreFdInfoKHR -> IO ()
writeField Ptr VkImportSemaphoreFdInfoKHR
p
          = Ptr VkImportSemaphoreFdInfoKHR -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkImportSemaphoreFdInfoKHR
p (Int
32)
{-# LINE 964 "src-gen/Graphics/Vulkan/Types/Struct/Import.hsc" #-}

instance Show VkImportSemaphoreFdInfoKHR where
        showsPrec :: Int -> VkImportSemaphoreFdInfoKHR -> ShowS
showsPrec Int
d VkImportSemaphoreFdInfoKHR
x
          = String -> ShowS
showString String
"VkImportSemaphoreFdInfoKHR {" 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 (VkImportSemaphoreFdInfoKHR
-> FieldType "sType" VkImportSemaphoreFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkImportSemaphoreFdInfoKHR
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 (VkImportSemaphoreFdInfoKHR
-> FieldType "pNext" VkImportSemaphoreFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkImportSemaphoreFdInfoKHR
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
"semaphore = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> VkSemaphore -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportSemaphoreFdInfoKHR
-> FieldType "semaphore" VkImportSemaphoreFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"semaphore" VkImportSemaphoreFdInfoKHR
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
"flags = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                  Int -> VkSemaphoreImportFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportSemaphoreFdInfoKHR
-> FieldType "flags" VkImportSemaphoreFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkImportSemaphoreFdInfoKHR
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
"handleType = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                        Int -> VkExternalSemaphoreHandleTypeFlagBits -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportSemaphoreFdInfoKHR
-> FieldType "handleType" VkImportSemaphoreFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"handleType" VkImportSemaphoreFdInfoKHR
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
"fd = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                                              Int -> CInt -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkImportSemaphoreFdInfoKHR
-> FieldType "fd" VkImportSemaphoreFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"fd" VkImportSemaphoreFdInfoKHR
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'