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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Export
       (VkExportFenceCreateInfo(..), VkExportFenceCreateInfoKHR,
        VkExportMemoryAllocateInfo(..), VkExportMemoryAllocateInfoKHR,
        VkExportMemoryAllocateInfoNV(..), VkExportSemaphoreCreateInfo(..),
        VkExportSemaphoreCreateInfoKHR)
       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      (VkExternalFenceHandleTypeFlags,
                                                           VkExternalMemoryHandleTypeFlags,
                                                           VkExternalMemoryHandleTypeFlagsNV,
                                                           VkExternalSemaphoreHandleTypeFlags)
import           Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import           Graphics.Vulkan.Types.Struct.Fence       (VkFenceCreateInfo)
import           Graphics.Vulkan.Types.Struct.Memory      (VkMemoryAllocateInfo)
import           Graphics.Vulkan.Types.Struct.Semaphore   (VkSemaphoreCreateInfo)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

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

instance Eq VkExportFenceCreateInfo where
        (VkExportFenceCreateInfo# Addr#
a ByteArray#
_) == :: VkExportFenceCreateInfo -> VkExportFenceCreateInfo -> Bool
== x :: VkExportFenceCreateInfo
x@(VkExportFenceCreateInfo# Addr#
b ByteArray#
_)
          = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkExportFenceCreateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkExportFenceCreateInfo
x) Addr#
a Addr#
b

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkExportFenceCreateInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
          = Addr# -> ByteArray# -> VkExportFenceCreateInfo
VkExportFenceCreateInfo# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkExportFenceCreateInfo where
        type StructFields VkExportFenceCreateInfo =
             '["sType", "pNext", "handleTypes"] -- ' closing tick for hsc2hs
        type CUnionType VkExportFenceCreateInfo = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkExportFenceCreateInfo = 'False -- ' closing tick for hsc2hs
        type StructExtends VkExportFenceCreateInfo = '[VkFenceCreateInfo] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

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

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkExportFenceCreateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportFenceCreateInfo
-> FieldType "sType" VkExportFenceCreateInfo -> IO ()
writeField Ptr VkExportFenceCreateInfo
p
          = Ptr VkExportFenceCreateInfo -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportFenceCreateInfo
p (Int
0)
{-# LINE 117 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

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

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkExportFenceCreateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportFenceCreateInfo
-> FieldType "pNext" VkExportFenceCreateInfo -> IO ()
writeField Ptr VkExportFenceCreateInfo
p
          = Ptr VkExportFenceCreateInfo -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportFenceCreateInfo
p (Int
8)
{-# LINE 148 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "handleTypes" VkExportFenceCreateInfo where
        type FieldType "handleTypes" VkExportFenceCreateInfo =
             VkExternalFenceHandleTypeFlags
        type FieldOptional "handleTypes" VkExportFenceCreateInfo = 'True -- ' closing tick for hsc2hs
        type FieldOffset "handleTypes" VkExportFenceCreateInfo =
             (16)
{-# LINE 156 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}
        type FieldIsArray "handleTypes" VkExportFenceCreateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
True

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkExportFenceCreateInfo
-> IO (FieldType "handleTypes" VkExportFenceCreateInfo)
readField Ptr VkExportFenceCreateInfo
p
          = Ptr VkExportFenceCreateInfo
-> Int -> IO VkExternalFenceHandleTypeFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkExportFenceCreateInfo
p (Int
16)
{-# LINE 175 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "handleTypes" VkExportFenceCreateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportFenceCreateInfo
-> FieldType "handleTypes" VkExportFenceCreateInfo -> IO ()
writeField Ptr VkExportFenceCreateInfo
p
          = Ptr VkExportFenceCreateInfo
-> Int -> VkExternalFenceHandleTypeFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportFenceCreateInfo
p (Int
16)
{-# LINE 181 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

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

-- | Alias for `VkExportFenceCreateInfo`
type VkExportFenceCreateInfoKHR = VkExportFenceCreateInfo

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

instance Eq VkExportMemoryAllocateInfo where
        (VkExportMemoryAllocateInfo# Addr#
a ByteArray#
_) == :: VkExportMemoryAllocateInfo -> VkExportMemoryAllocateInfo -> Bool
==
          x :: VkExportMemoryAllocateInfo
x@(VkExportMemoryAllocateInfo# Addr#
b ByteArray#
_)
          = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkExportMemoryAllocateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkExportMemoryAllocateInfo
x) Addr#
a Addr#
b

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkExportMemoryAllocateInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
          = Addr# -> ByteArray# -> VkExportMemoryAllocateInfo
VkExportMemoryAllocateInfo#
              (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
              ByteArray#
b

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

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

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkExportMemoryAllocateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportMemoryAllocateInfo
-> FieldType "sType" VkExportMemoryAllocateInfo -> IO ()
writeField Ptr VkExportMemoryAllocateInfo
p
          = Ptr VkExportMemoryAllocateInfo -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportMemoryAllocateInfo
p (Int
0)
{-# LINE 287 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

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

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkExportMemoryAllocateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportMemoryAllocateInfo
-> FieldType "pNext" VkExportMemoryAllocateInfo -> IO ()
writeField Ptr VkExportMemoryAllocateInfo
p
          = Ptr VkExportMemoryAllocateInfo -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportMemoryAllocateInfo
p (Int
8)
{-# LINE 319 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "handleTypes" VkExportMemoryAllocateInfo where
        type FieldType "handleTypes" VkExportMemoryAllocateInfo =
             VkExternalMemoryHandleTypeFlags
        type FieldOptional "handleTypes" VkExportMemoryAllocateInfo = 'True -- ' closing tick for hsc2hs
        type FieldOffset "handleTypes" VkExportMemoryAllocateInfo =
             (16)
{-# LINE 327 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}
        type FieldIsArray "handleTypes" VkExportMemoryAllocateInfo = 'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
True

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkExportMemoryAllocateInfo
-> IO (FieldType "handleTypes" VkExportMemoryAllocateInfo)
readField Ptr VkExportMemoryAllocateInfo
p
          = Ptr VkExportMemoryAllocateInfo
-> Int -> IO VkExternalMemoryHandleTypeFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkExportMemoryAllocateInfo
p (Int
16)
{-# LINE 346 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "handleTypes" VkExportMemoryAllocateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportMemoryAllocateInfo
-> FieldType "handleTypes" VkExportMemoryAllocateInfo -> IO ()
writeField Ptr VkExportMemoryAllocateInfo
p
          = Ptr VkExportMemoryAllocateInfo
-> Int -> VkExternalMemoryHandleTypeFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportMemoryAllocateInfo
p (Int
16)
{-# LINE 352 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

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

-- | Alias for `VkExportMemoryAllocateInfo`
type VkExportMemoryAllocateInfoKHR = VkExportMemoryAllocateInfo

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

instance Eq VkExportMemoryAllocateInfoNV where
        (VkExportMemoryAllocateInfoNV# Addr#
a ByteArray#
_) == :: VkExportMemoryAllocateInfoNV
-> VkExportMemoryAllocateInfoNV -> Bool
==
          x :: VkExportMemoryAllocateInfoNV
x@(VkExportMemoryAllocateInfoNV# Addr#
b ByteArray#
_)
          = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkExportMemoryAllocateInfoNV -> Int
forall a. Storable a => a -> Int
sizeOf VkExportMemoryAllocateInfoNV
x) Addr#
a Addr#
b

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkExportMemoryAllocateInfoNV
unsafeFromByteArrayOffset Int#
off ByteArray#
b
          = Addr# -> ByteArray# -> VkExportMemoryAllocateInfoNV
VkExportMemoryAllocateInfoNV#
              (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
              ByteArray#
b

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

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

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkExportMemoryAllocateInfoNV where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportMemoryAllocateInfoNV
-> FieldType "sType" VkExportMemoryAllocateInfoNV -> IO ()
writeField Ptr VkExportMemoryAllocateInfoNV
p
          = Ptr VkExportMemoryAllocateInfoNV -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportMemoryAllocateInfoNV
p (Int
0)
{-# LINE 460 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

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

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkExportMemoryAllocateInfoNV where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportMemoryAllocateInfoNV
-> FieldType "pNext" VkExportMemoryAllocateInfoNV -> IO ()
writeField Ptr VkExportMemoryAllocateInfoNV
p
          = Ptr VkExportMemoryAllocateInfoNV -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportMemoryAllocateInfoNV
p (Int
8)
{-# LINE 492 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "handleTypes" VkExportMemoryAllocateInfoNV where
        type FieldType "handleTypes" VkExportMemoryAllocateInfoNV =
             VkExternalMemoryHandleTypeFlagsNV
        type FieldOptional "handleTypes" VkExportMemoryAllocateInfoNV =
             'True -- ' closing tick for hsc2hs
        type FieldOffset "handleTypes" VkExportMemoryAllocateInfoNV =
             (16)
{-# LINE 501 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}
        type FieldIsArray "handleTypes" VkExportMemoryAllocateInfoNV =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
True

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkExportMemoryAllocateInfoNV
-> IO (FieldType "handleTypes" VkExportMemoryAllocateInfoNV)
readField Ptr VkExportMemoryAllocateInfoNV
p
          = Ptr VkExportMemoryAllocateInfoNV
-> Int -> IO VkExternalMemoryHandleTypeFlagsNV
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkExportMemoryAllocateInfoNV
p (Int
16)
{-# LINE 521 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "handleTypes" VkExportMemoryAllocateInfoNV where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportMemoryAllocateInfoNV
-> FieldType "handleTypes" VkExportMemoryAllocateInfoNV -> IO ()
writeField Ptr VkExportMemoryAllocateInfoNV
p
          = Ptr VkExportMemoryAllocateInfoNV
-> Int -> VkExternalMemoryHandleTypeFlagsNV -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportMemoryAllocateInfoNV
p (Int
16)
{-# LINE 527 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

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

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

instance Eq VkExportSemaphoreCreateInfo where
        (VkExportSemaphoreCreateInfo# Addr#
a ByteArray#
_) == :: VkExportSemaphoreCreateInfo -> VkExportSemaphoreCreateInfo -> Bool
==
          x :: VkExportSemaphoreCreateInfo
x@(VkExportSemaphoreCreateInfo# Addr#
b ByteArray#
_)
          = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkExportSemaphoreCreateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkExportSemaphoreCreateInfo
x) Addr#
a Addr#
b

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

        {-# INLINE unsafeByteArray #-}
        unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkExportSemaphoreCreateInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
          = Addr# -> ByteArray# -> VkExportSemaphoreCreateInfo
VkExportSemaphoreCreateInfo#
              (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
              ByteArray#
b

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkExportSemaphoreCreateInfo where
        type StructFields VkExportSemaphoreCreateInfo =
             '["sType", "pNext", "handleTypes"] -- ' closing tick for hsc2hs
        type CUnionType VkExportSemaphoreCreateInfo = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkExportSemaphoreCreateInfo = 'False -- ' closing tick for hsc2hs
        type StructExtends VkExportSemaphoreCreateInfo =
             '[VkSemaphoreCreateInfo] -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

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

instance {-# OVERLAPPING #-}
         CanWriteField "sType" VkExportSemaphoreCreateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportSemaphoreCreateInfo
-> FieldType "sType" VkExportSemaphoreCreateInfo -> IO ()
writeField Ptr VkExportSemaphoreCreateInfo
p
          = Ptr VkExportSemaphoreCreateInfo -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportSemaphoreCreateInfo
p (Int
0)
{-# LINE 631 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

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

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
False

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

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

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

instance {-# OVERLAPPING #-}
         CanWriteField "pNext" VkExportSemaphoreCreateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportSemaphoreCreateInfo
-> FieldType "pNext" VkExportSemaphoreCreateInfo -> IO ()
writeField Ptr VkExportSemaphoreCreateInfo
p
          = Ptr VkExportSemaphoreCreateInfo -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportSemaphoreCreateInfo
p (Int
8)
{-# LINE 663 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "handleTypes" VkExportSemaphoreCreateInfo where
        type FieldType "handleTypes" VkExportSemaphoreCreateInfo =
             VkExternalSemaphoreHandleTypeFlags
        type FieldOptional "handleTypes" VkExportSemaphoreCreateInfo =
             'True -- ' closing tick for hsc2hs
        type FieldOffset "handleTypes" VkExportSemaphoreCreateInfo =
             (16)
{-# LINE 672 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}
        type FieldIsArray "handleTypes" VkExportSemaphoreCreateInfo =
             'False -- ' closing tick for hsc2hs

        {-# INLINE fieldOptional #-}
        fieldOptional :: Bool
fieldOptional = Bool
True

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkExportSemaphoreCreateInfo
-> IO (FieldType "handleTypes" VkExportSemaphoreCreateInfo)
readField Ptr VkExportSemaphoreCreateInfo
p
          = Ptr VkExportSemaphoreCreateInfo
-> Int -> IO VkExternalSemaphoreHandleTypeFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkExportSemaphoreCreateInfo
p (Int
16)
{-# LINE 692 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "handleTypes" VkExportSemaphoreCreateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkExportSemaphoreCreateInfo
-> FieldType "handleTypes" VkExportSemaphoreCreateInfo -> IO ()
writeField Ptr VkExportSemaphoreCreateInfo
p
          = Ptr VkExportSemaphoreCreateInfo
-> Int -> VkExternalSemaphoreHandleTypeFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkExportSemaphoreCreateInfo
p (Int
16)
{-# LINE 698 "src-gen/Graphics/Vulkan/Types/Struct/Export.hsc" #-}

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

-- | Alias for `VkExportSemaphoreCreateInfo`
type VkExportSemaphoreCreateInfoKHR = VkExportSemaphoreCreateInfo