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


{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE MagicHash             #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict                #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE TypeFamilies          #-}
module Graphics.Vulkan.Types.Struct.Memory
       (VkMemoryAllocateFlagsInfo(..), VkMemoryAllocateFlagsInfoKHR,
        VkMemoryAllocateInfo(..), VkMemoryBarrier(..),
        VkMemoryDedicatedAllocateInfo(..),
        VkMemoryDedicatedAllocateInfoKHR,
        VkMemoryDedicatedRequirements(..),
        VkMemoryDedicatedRequirementsKHR, VkMemoryFdPropertiesKHR(..),
        VkMemoryGetFdInfoKHR(..), VkMemoryHeap(..),
        VkMemoryHostPointerPropertiesEXT(..), VkMemoryRequirements(..),
        VkMemoryRequirements2(..), VkMemoryRequirements2KHR,
        VkMemoryType(..))
       where
import           Foreign.Storable                         (Storable (..))
import           GHC.Base                                 (Addr#, ByteArray#,
                                                           byteArrayContents#,
                                                           plusAddr#)
import           Graphics.Vulkan.Marshal
import           Graphics.Vulkan.Marshal.Internal
import           Graphics.Vulkan.Types.BaseTypes          (VkBool32,
                                                           VkDeviceSize)
import           Graphics.Vulkan.Types.Enum.AccessFlags   (VkAccessFlags)
import           Graphics.Vulkan.Types.Enum.External      (VkExternalMemoryHandleTypeFlagBits)
import           Graphics.Vulkan.Types.Enum.Memory        (VkMemoryAllocateFlags,
                                                           VkMemoryHeapFlags,
                                                           VkMemoryPropertyFlags)
import           Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import           Graphics.Vulkan.Types.Handles            (VkBuffer,
                                                           VkDeviceMemory,
                                                           VkImage)
import           System.IO.Unsafe                         (unsafeDupablePerformIO)

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "flags" VkMemoryAllocateFlagsInfo where
        type FieldType "flags" VkMemoryAllocateFlagsInfo =
             VkMemoryAllocateFlags
        type FieldOptional "flags" VkMemoryAllocateFlagsInfo = 'True -- ' closing tick for hsc2hs
        type FieldOffset "flags" VkMemoryAllocateFlagsInfo =
             (16)
{-# LINE 170 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "flags" VkMemoryAllocateFlagsInfo = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryAllocateFlagsInfo
-> IO (FieldType "flags" VkMemoryAllocateFlagsInfo)
readField Ptr VkMemoryAllocateFlagsInfo
p
          = Ptr VkMemoryAllocateFlagsInfo -> Int -> IO VkMemoryAllocateFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryAllocateFlagsInfo
p (Int
16)
{-# LINE 189 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "flags" VkMemoryAllocateFlagsInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryAllocateFlagsInfo
-> FieldType "flags" VkMemoryAllocateFlagsInfo -> IO ()
writeField Ptr VkMemoryAllocateFlagsInfo
p
          = Ptr VkMemoryAllocateFlagsInfo
-> Int -> VkMemoryAllocateFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryAllocateFlagsInfo
p (Int
16)
{-# LINE 195 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "deviceMask" VkMemoryAllocateFlagsInfo where
        type FieldType "deviceMask" VkMemoryAllocateFlagsInfo = Word32
        type FieldOptional "deviceMask" VkMemoryAllocateFlagsInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "deviceMask" VkMemoryAllocateFlagsInfo =
             (20)
{-# LINE 202 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "deviceMask" VkMemoryAllocateFlagsInfo = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryAllocateFlagsInfo
-> IO (FieldType "deviceMask" VkMemoryAllocateFlagsInfo)
readField Ptr VkMemoryAllocateFlagsInfo
p
          = Ptr VkMemoryAllocateFlagsInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryAllocateFlagsInfo
p (Int
20)
{-# LINE 221 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "deviceMask" VkMemoryAllocateFlagsInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryAllocateFlagsInfo
-> FieldType "deviceMask" VkMemoryAllocateFlagsInfo -> IO ()
writeField Ptr VkMemoryAllocateFlagsInfo
p
          = Ptr VkMemoryAllocateFlagsInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryAllocateFlagsInfo
p (Int
20)
{-# LINE 227 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

-- | Alias for `VkMemoryAllocateFlagsInfo`
type VkMemoryAllocateFlagsInfoKHR = VkMemoryAllocateFlagsInfo

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "allocationSize" VkMemoryAllocateInfo where
        type FieldType "allocationSize" VkMemoryAllocateInfo = VkDeviceSize
        type FieldOptional "allocationSize" VkMemoryAllocateInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "allocationSize" VkMemoryAllocateInfo =
             (16)
{-# LINE 369 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "allocationSize" VkMemoryAllocateInfo = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryAllocateInfo
-> IO (FieldType "allocationSize" VkMemoryAllocateInfo)
readField Ptr VkMemoryAllocateInfo
p
          = Ptr VkMemoryAllocateInfo -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryAllocateInfo
p (Int
16)
{-# LINE 388 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "allocationSize" VkMemoryAllocateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryAllocateInfo
-> FieldType "allocationSize" VkMemoryAllocateInfo -> IO ()
writeField Ptr VkMemoryAllocateInfo
p
          = Ptr VkMemoryAllocateInfo -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryAllocateInfo
p (Int
16)
{-# LINE 394 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "memoryTypeIndex" VkMemoryAllocateInfo where
        type FieldType "memoryTypeIndex" VkMemoryAllocateInfo = Word32
        type FieldOptional "memoryTypeIndex" VkMemoryAllocateInfo = 'False -- ' closing tick for hsc2hs
        type FieldOffset "memoryTypeIndex" VkMemoryAllocateInfo =
             (24)
{-# LINE 401 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "memoryTypeIndex" VkMemoryAllocateInfo = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryAllocateInfo
-> IO (FieldType "memoryTypeIndex" VkMemoryAllocateInfo)
readField Ptr VkMemoryAllocateInfo
p
          = Ptr VkMemoryAllocateInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryAllocateInfo
p (Int
24)
{-# LINE 420 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "memoryTypeIndex" VkMemoryAllocateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryAllocateInfo
-> FieldType "memoryTypeIndex" VkMemoryAllocateInfo -> IO ()
writeField Ptr VkMemoryAllocateInfo
p
          = Ptr VkMemoryAllocateInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryAllocateInfo
p (Int
24)
{-# LINE 426 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkMemoryBarrier where
        type StructFields VkMemoryBarrier =
             '["sType", "pNext", "srcAccessMask", "dstAccessMask"] -- ' closing tick for hsc2hs
        type CUnionType VkMemoryBarrier = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkMemoryBarrier = 'False -- ' closing tick for hsc2hs
        type StructExtends VkMemoryBarrier = '[] -- ' closing tick for hsc2hs

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

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

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

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

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

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

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

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

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "srcAccessMask" VkMemoryBarrier where
        type FieldType "srcAccessMask" VkMemoryBarrier = VkAccessFlags
        type FieldOptional "srcAccessMask" VkMemoryBarrier = 'True -- ' closing tick for hsc2hs
        type FieldOffset "srcAccessMask" VkMemoryBarrier =
             (16)
{-# LINE 563 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "srcAccessMask" VkMemoryBarrier = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryBarrier
-> IO (FieldType "srcAccessMask" VkMemoryBarrier)
readField Ptr VkMemoryBarrier
p
          = Ptr VkMemoryBarrier -> Int -> IO VkAccessFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryBarrier
p (Int
16)
{-# LINE 581 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "srcAccessMask" VkMemoryBarrier where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryBarrier
-> FieldType "srcAccessMask" VkMemoryBarrier -> IO ()
writeField Ptr VkMemoryBarrier
p
          = Ptr VkMemoryBarrier -> Int -> VkAccessFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryBarrier
p (Int
16)
{-# LINE 587 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "dstAccessMask" VkMemoryBarrier where
        type FieldType "dstAccessMask" VkMemoryBarrier = VkAccessFlags
        type FieldOptional "dstAccessMask" VkMemoryBarrier = 'True -- ' closing tick for hsc2hs
        type FieldOffset "dstAccessMask" VkMemoryBarrier =
             (20)
{-# LINE 594 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "dstAccessMask" VkMemoryBarrier = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryBarrier
-> IO (FieldType "dstAccessMask" VkMemoryBarrier)
readField Ptr VkMemoryBarrier
p
          = Ptr VkMemoryBarrier -> Int -> IO VkAccessFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryBarrier
p (Int
20)
{-# LINE 612 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "dstAccessMask" VkMemoryBarrier where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryBarrier
-> FieldType "dstAccessMask" VkMemoryBarrier -> IO ()
writeField Ptr VkMemoryBarrier
p
          = Ptr VkMemoryBarrier -> Int -> VkAccessFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryBarrier
p (Int
20)
{-# LINE 618 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryDedicatedAllocateInfo
-> IO (FieldType "image" VkMemoryDedicatedAllocateInfo)
readField Ptr VkMemoryDedicatedAllocateInfo
p
          = Ptr VkMemoryDedicatedAllocateInfo -> Int -> IO VkImage
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryDedicatedAllocateInfo
p (Int
16)
{-# LINE 785 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "image" VkMemoryDedicatedAllocateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryDedicatedAllocateInfo
-> FieldType "image" VkMemoryDedicatedAllocateInfo -> IO ()
writeField Ptr VkMemoryDedicatedAllocateInfo
p
          = Ptr VkMemoryDedicatedAllocateInfo -> Int -> VkImage -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryDedicatedAllocateInfo
p (Int
16)
{-# LINE 791 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryDedicatedAllocateInfo
-> IO (FieldType "buffer" VkMemoryDedicatedAllocateInfo)
readField Ptr VkMemoryDedicatedAllocateInfo
p
          = Ptr VkMemoryDedicatedAllocateInfo -> Int -> IO VkBuffer
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryDedicatedAllocateInfo
p (Int
24)
{-# LINE 817 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "buffer" VkMemoryDedicatedAllocateInfo where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryDedicatedAllocateInfo
-> FieldType "buffer" VkMemoryDedicatedAllocateInfo -> IO ()
writeField Ptr VkMemoryDedicatedAllocateInfo
p
          = Ptr VkMemoryDedicatedAllocateInfo -> Int -> VkBuffer -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryDedicatedAllocateInfo
p (Int
24)
{-# LINE 823 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

-- | Alias for `VkMemoryDedicatedAllocateInfo`
type VkMemoryDedicatedAllocateInfoKHR =
     VkMemoryDedicatedAllocateInfo

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkMemoryDedicatedRequirements where
        type StructFields VkMemoryDedicatedRequirements =
             '["sType", "pNext", "prefersDedicatedAllocation", -- ' closing tick for hsc2hs
               "requiresDedicatedAllocation"]
        type CUnionType VkMemoryDedicatedRequirements = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkMemoryDedicatedRequirements = 'True -- ' closing tick for hsc2hs
        type StructExtends VkMemoryDedicatedRequirements =
             '[VkMemoryRequirements2] -- ' closing tick for hsc2hs

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryDedicatedRequirements
-> IO
     (FieldType
        "prefersDedicatedAllocation" VkMemoryDedicatedRequirements)
readField Ptr VkMemoryDedicatedRequirements
p
          = Ptr VkMemoryDedicatedRequirements -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryDedicatedRequirements
p (Int
16)
{-# LINE 1006 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "prefersDedicatedAllocation"
           VkMemoryDedicatedRequirements
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryDedicatedRequirements
-> FieldType
     "prefersDedicatedAllocation" VkMemoryDedicatedRequirements
-> IO ()
writeField Ptr VkMemoryDedicatedRequirements
p
          = Ptr VkMemoryDedicatedRequirements -> Int -> VkBool32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryDedicatedRequirements
p (Int
16)
{-# LINE 1014 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "requiresDedicatedAllocation"
           VkMemoryDedicatedRequirements
         where
        type FieldType "requiresDedicatedAllocation"
               VkMemoryDedicatedRequirements
             = VkBool32
        type FieldOptional "requiresDedicatedAllocation"
               VkMemoryDedicatedRequirements
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "requiresDedicatedAllocation"
               VkMemoryDedicatedRequirements
             =
             (20)
{-# LINE 1029 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "requiresDedicatedAllocation"
               VkMemoryDedicatedRequirements
             = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryDedicatedRequirements
-> IO
     (FieldType
        "requiresDedicatedAllocation" VkMemoryDedicatedRequirements)
readField Ptr VkMemoryDedicatedRequirements
p
          = Ptr VkMemoryDedicatedRequirements -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryDedicatedRequirements
p (Int
20)
{-# LINE 1052 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "requiresDedicatedAllocation"
           VkMemoryDedicatedRequirements
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryDedicatedRequirements
-> FieldType
     "requiresDedicatedAllocation" VkMemoryDedicatedRequirements
-> IO ()
writeField Ptr VkMemoryDedicatedRequirements
p
          = Ptr VkMemoryDedicatedRequirements -> Int -> VkBool32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryDedicatedRequirements
p (Int
20)
{-# LINE 1060 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

-- | Alias for `VkMemoryDedicatedRequirements`
type VkMemoryDedicatedRequirementsKHR =
     VkMemoryDedicatedRequirements

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "memoryTypeBits" VkMemoryFdPropertiesKHR where
        type FieldType "memoryTypeBits" VkMemoryFdPropertiesKHR = Word32
        type FieldOptional "memoryTypeBits" VkMemoryFdPropertiesKHR =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "memoryTypeBits" VkMemoryFdPropertiesKHR =
             (16)
{-# LINE 1205 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "memoryTypeBits" VkMemoryFdPropertiesKHR = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryFdPropertiesKHR
-> IO (FieldType "memoryTypeBits" VkMemoryFdPropertiesKHR)
readField Ptr VkMemoryFdPropertiesKHR
p
          = Ptr VkMemoryFdPropertiesKHR -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryFdPropertiesKHR
p (Int
16)
{-# LINE 1224 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "memoryTypeBits" VkMemoryFdPropertiesKHR where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryFdPropertiesKHR
-> FieldType "memoryTypeBits" VkMemoryFdPropertiesKHR -> IO ()
writeField Ptr VkMemoryFdPropertiesKHR
p
          = Ptr VkMemoryFdPropertiesKHR -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryFdPropertiesKHR
p (Int
16)
{-# LINE 1230 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

instance {-# OVERLAPPING #-} HasField "memory" VkMemoryGetFdInfoKHR
         where
        type FieldType "memory" VkMemoryGetFdInfoKHR = VkDeviceMemory
        type FieldOptional "memory" VkMemoryGetFdInfoKHR = 'False -- ' closing tick for hsc2hs
        type FieldOffset "memory" VkMemoryGetFdInfoKHR =
             (16)
{-# LINE 1366 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "memory" VkMemoryGetFdInfoKHR = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryGetFdInfoKHR
-> IO (FieldType "memory" VkMemoryGetFdInfoKHR)
readField Ptr VkMemoryGetFdInfoKHR
p
          = Ptr VkMemoryGetFdInfoKHR -> Int -> IO VkDeviceMemory
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryGetFdInfoKHR
p (Int
16)
{-# LINE 1384 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "memory" VkMemoryGetFdInfoKHR where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryGetFdInfoKHR
-> FieldType "memory" VkMemoryGetFdInfoKHR -> IO ()
writeField Ptr VkMemoryGetFdInfoKHR
p
          = Ptr VkMemoryGetFdInfoKHR -> Int -> VkDeviceMemory -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryGetFdInfoKHR
p (Int
16)
{-# LINE 1390 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

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

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

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

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

instance {-# OVERLAPPING #-}
         CanWriteField "handleType" VkMemoryGetFdInfoKHR where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryGetFdInfoKHR
-> FieldType "handleType" VkMemoryGetFdInfoKHR -> IO ()
writeField Ptr VkMemoryGetFdInfoKHR
p
          = Ptr VkMemoryGetFdInfoKHR
-> Int -> VkExternalMemoryHandleTypeFlagBits -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryGetFdInfoKHR
p (Int
24)
{-# LINE 1423 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

-- | > typedef struct VkMemoryHeap {
--   >     VkDeviceSize           size;
--   >     VkMemoryHeapFlags      flags;
--   > } VkMemoryHeap;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkMemoryHeap VkMemoryHeap registry at www.khronos.org>
data VkMemoryHeap = VkMemoryHeap# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkMemoryHeap where
        sizeOf :: VkMemoryHeap -> Int
sizeOf ~VkMemoryHeap
_ = (Int
16)
{-# LINE 1461 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkMemoryHeap where
        type StructFields VkMemoryHeap = '["size", "flags"] -- ' closing tick for hsc2hs
        type CUnionType VkMemoryHeap = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkMemoryHeap = 'True -- ' closing tick for hsc2hs
        type StructExtends VkMemoryHeap = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "size" VkMemoryHeap where
        type FieldType "size" VkMemoryHeap = VkDeviceSize
        type FieldOptional "size" VkMemoryHeap = 'False -- ' closing tick for hsc2hs
        type FieldOffset "size" VkMemoryHeap =
             (0)
{-# LINE 1496 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "size" VkMemoryHeap = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryHeap -> IO (FieldType "size" VkMemoryHeap)
readField Ptr VkMemoryHeap
p
          = Ptr VkMemoryHeap -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryHeap
p (Int
0)
{-# LINE 1513 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "size" VkMemoryHeap
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryHeap -> FieldType "size" VkMemoryHeap -> IO ()
writeField Ptr VkMemoryHeap
p
          = Ptr VkMemoryHeap -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryHeap
p (Int
0)
{-# LINE 1519 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-} HasField "flags" VkMemoryHeap where
        type FieldType "flags" VkMemoryHeap = VkMemoryHeapFlags
        type FieldOptional "flags" VkMemoryHeap = 'True -- ' closing tick for hsc2hs
        type FieldOffset "flags" VkMemoryHeap =
             (8)
{-# LINE 1525 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "flags" VkMemoryHeap = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryHeap -> IO (FieldType "flags" VkMemoryHeap)
readField Ptr VkMemoryHeap
p
          = Ptr VkMemoryHeap -> Int -> IO VkMemoryHeapFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryHeap
p (Int
8)
{-# LINE 1543 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "flags" VkMemoryHeap
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryHeap -> FieldType "flags" VkMemoryHeap -> IO ()
writeField Ptr VkMemoryHeap
p
          = Ptr VkMemoryHeap -> Int -> VkMemoryHeapFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryHeap
p (Int
8)
{-# LINE 1549 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance Show VkMemoryHeap where
        showsPrec :: Int -> VkMemoryHeap -> ShowS
showsPrec Int
d VkMemoryHeap
x
          = String -> ShowS
showString String
"VkMemoryHeap {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"size = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkDeviceSize -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMemoryHeap -> FieldType "size" VkMemoryHeap
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"size" VkMemoryHeap
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 -> VkMemoryHeapFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMemoryHeap -> FieldType "flags" VkMemoryHeap
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkMemoryHeap
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "memoryTypeBits" VkMemoryHostPointerPropertiesEXT where
        type FieldType "memoryTypeBits" VkMemoryHostPointerPropertiesEXT =
             Word32
        type FieldOptional "memoryTypeBits"
               VkMemoryHostPointerPropertiesEXT
             = 'False -- ' closing tick for hsc2hs
        type FieldOffset "memoryTypeBits" VkMemoryHostPointerPropertiesEXT
             =
             (16)
{-# LINE 1696 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "memoryTypeBits" VkMemoryHostPointerPropertiesEXT
             = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryHostPointerPropertiesEXT
-> IO (FieldType "memoryTypeBits" VkMemoryHostPointerPropertiesEXT)
readField Ptr VkMemoryHostPointerPropertiesEXT
p
          = Ptr VkMemoryHostPointerPropertiesEXT -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryHostPointerPropertiesEXT
p (Int
16)
{-# LINE 1717 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "memoryTypeBits" VkMemoryHostPointerPropertiesEXT
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryHostPointerPropertiesEXT
-> FieldType "memoryTypeBits" VkMemoryHostPointerPropertiesEXT
-> IO ()
writeField Ptr VkMemoryHostPointerPropertiesEXT
p
          = Ptr VkMemoryHostPointerPropertiesEXT -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryHostPointerPropertiesEXT
p (Int
16)
{-# LINE 1724 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

-- | > typedef struct VkMemoryRequirements {
--   >     VkDeviceSize           size;
--   >     VkDeviceSize           alignment;
--   >     uint32_t               memoryTypeBits;
--   > } VkMemoryRequirements;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkMemoryRequirements VkMemoryRequirements registry at www.khronos.org>
data VkMemoryRequirements = VkMemoryRequirements# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkMemoryRequirements where
        type StructFields VkMemoryRequirements =
             '["size", "alignment", "memoryTypeBits"] -- ' closing tick for hsc2hs
        type CUnionType VkMemoryRequirements = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkMemoryRequirements = 'True -- ' closing tick for hsc2hs
        type StructExtends VkMemoryRequirements = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "size" VkMemoryRequirements
         where
        type FieldType "size" VkMemoryRequirements = VkDeviceSize
        type FieldOptional "size" VkMemoryRequirements = 'False -- ' closing tick for hsc2hs
        type FieldOffset "size" VkMemoryRequirements =
             (0)
{-# LINE 1797 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "size" VkMemoryRequirements = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryRequirements
-> IO (FieldType "size" VkMemoryRequirements)
readField Ptr VkMemoryRequirements
p
          = Ptr VkMemoryRequirements -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryRequirements
p (Int
0)
{-# LINE 1815 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "size" VkMemoryRequirements where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryRequirements
-> FieldType "size" VkMemoryRequirements -> IO ()
writeField Ptr VkMemoryRequirements
p
          = Ptr VkMemoryRequirements -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryRequirements
p (Int
0)
{-# LINE 1821 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "alignment" VkMemoryRequirements where
        type FieldType "alignment" VkMemoryRequirements = VkDeviceSize
        type FieldOptional "alignment" VkMemoryRequirements = 'False -- ' closing tick for hsc2hs
        type FieldOffset "alignment" VkMemoryRequirements =
             (8)
{-# LINE 1828 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "alignment" VkMemoryRequirements = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryRequirements
-> IO (FieldType "alignment" VkMemoryRequirements)
readField Ptr VkMemoryRequirements
p
          = Ptr VkMemoryRequirements -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryRequirements
p (Int
8)
{-# LINE 1846 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "alignment" VkMemoryRequirements where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryRequirements
-> FieldType "alignment" VkMemoryRequirements -> IO ()
writeField Ptr VkMemoryRequirements
p
          = Ptr VkMemoryRequirements -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryRequirements
p (Int
8)
{-# LINE 1852 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         HasField "memoryTypeBits" VkMemoryRequirements where
        type FieldType "memoryTypeBits" VkMemoryRequirements = Word32
        type FieldOptional "memoryTypeBits" VkMemoryRequirements = 'False -- ' closing tick for hsc2hs
        type FieldOffset "memoryTypeBits" VkMemoryRequirements =
             (16)
{-# LINE 1859 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "memoryTypeBits" VkMemoryRequirements = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryRequirements
-> IO (FieldType "memoryTypeBits" VkMemoryRequirements)
readField Ptr VkMemoryRequirements
p
          = Ptr VkMemoryRequirements -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryRequirements
p (Int
16)
{-# LINE 1878 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "memoryTypeBits" VkMemoryRequirements where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryRequirements
-> FieldType "memoryTypeBits" VkMemoryRequirements -> IO ()
writeField Ptr VkMemoryRequirements
p
          = Ptr VkMemoryRequirements -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryRequirements
p (Int
16)
{-# LINE 1884 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance Show VkMemoryRequirements where
        showsPrec :: Int -> VkMemoryRequirements -> ShowS
showsPrec Int
d VkMemoryRequirements
x
          = String -> ShowS
showString String
"VkMemoryRequirements {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"size = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkDeviceSize -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMemoryRequirements -> FieldType "size" VkMemoryRequirements
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"size" VkMemoryRequirements
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
"alignment = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> VkDeviceSize -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMemoryRequirements -> FieldType "alignment" VkMemoryRequirements
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"alignment" VkMemoryRequirements
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
"memoryTypeBits = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                            Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMemoryRequirements
-> FieldType "memoryTypeBits" VkMemoryRequirements
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"memoryTypeBits" VkMemoryRequirements
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'

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

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

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

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

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

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

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

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

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

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

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

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

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

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

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

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

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

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

instance {-# OVERLAPPING #-}
         HasField "memoryRequirements" VkMemoryRequirements2 where
        type FieldType "memoryRequirements" VkMemoryRequirements2 =
             VkMemoryRequirements
        type FieldOptional "memoryRequirements" VkMemoryRequirements2 =
             'False -- ' closing tick for hsc2hs
        type FieldOffset "memoryRequirements" VkMemoryRequirements2 =
             (16)
{-# LINE 2022 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "memoryRequirements" VkMemoryRequirements2 =
             'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryRequirements2
-> IO (FieldType "memoryRequirements" VkMemoryRequirements2)
readField Ptr VkMemoryRequirements2
p
          = Ptr VkMemoryRequirements2 -> Int -> IO VkMemoryRequirements
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryRequirements2
p (Int
16)
{-# LINE 2042 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "memoryRequirements" VkMemoryRequirements2 where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryRequirements2
-> FieldType "memoryRequirements" VkMemoryRequirements2 -> IO ()
writeField Ptr VkMemoryRequirements2
p
          = Ptr VkMemoryRequirements2 -> Int -> VkMemoryRequirements -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryRequirements2
p (Int
16)
{-# LINE 2048 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

-- | Alias for `VkMemoryRequirements2`
type VkMemoryRequirements2KHR = VkMemoryRequirements2

-- | > typedef struct VkMemoryType {
--   >     VkMemoryPropertyFlags  propertyFlags;
--   >     uint32_t               heapIndex;
--   > } VkMemoryType;
--
--   <https://www.khronos.org/registry/vulkan/specs/1.1-extensions/html/vkspec.html#VkMemoryType VkMemoryType registry at www.khronos.org>
data VkMemoryType = VkMemoryType# Addr# ByteArray#

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

        {-# INLINE (==) #-}

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

        {-# INLINE compare #-}

instance Storable VkMemoryType where
        sizeOf :: VkMemoryType -> Int
sizeOf ~VkMemoryType
_ = (Int
8)
{-# LINE 2086 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

        {-# INLINE sizeOf #-}
        alignment :: VkMemoryType -> Int
alignment ~VkMemoryType
_ = Int
4
{-# LINE 2089 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

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

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

        {-# INLINE poke #-}

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

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

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

        {-# INLINE unsafeFromByteArrayOffset #-}

instance VulkanMarshal VkMemoryType where
        type StructFields VkMemoryType = '["propertyFlags", "heapIndex"] -- ' closing tick for hsc2hs
        type CUnionType VkMemoryType = 'False -- ' closing tick for hsc2hs
        type ReturnedOnly VkMemoryType = 'True -- ' closing tick for hsc2hs
        type StructExtends VkMemoryType = '[] -- ' closing tick for hsc2hs

instance {-# OVERLAPPING #-} HasField "propertyFlags" VkMemoryType
         where
        type FieldType "propertyFlags" VkMemoryType = VkMemoryPropertyFlags
        type FieldOptional "propertyFlags" VkMemoryType = 'True -- ' closing tick for hsc2hs
        type FieldOffset "propertyFlags" VkMemoryType =
             (0)
{-# LINE 2122 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "propertyFlags" VkMemoryType = 'False -- ' closing tick for hsc2hs

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

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

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

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryType -> IO (FieldType "propertyFlags" VkMemoryType)
readField Ptr VkMemoryType
p
          = Ptr VkMemoryType -> Int -> IO VkMemoryPropertyFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryType
p (Int
0)
{-# LINE 2140 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-}
         CanWriteField "propertyFlags" VkMemoryType where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryType -> FieldType "propertyFlags" VkMemoryType -> IO ()
writeField Ptr VkMemoryType
p
          = Ptr VkMemoryType -> Int -> VkMemoryPropertyFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryType
p (Int
0)
{-# LINE 2146 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-} HasField "heapIndex" VkMemoryType
         where
        type FieldType "heapIndex" VkMemoryType = Word32
        type FieldOptional "heapIndex" VkMemoryType = 'False -- ' closing tick for hsc2hs
        type FieldOffset "heapIndex" VkMemoryType =
             (4)
{-# LINE 2153 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}
        type FieldIsArray "heapIndex" VkMemoryType = 'False -- ' closing tick for hsc2hs

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

        {-# INLINE fieldOffset #-}
        fieldOffset :: Int
fieldOffset = (Int
4)
{-# LINE 2160 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-} CanReadField "heapIndex" VkMemoryType
         where
        {-# NOINLINE getField #-}
        getField :: VkMemoryType -> FieldType "heapIndex" VkMemoryType
getField VkMemoryType
x
          = IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
              (Ptr VkMemoryType -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkMemoryType -> Ptr VkMemoryType
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkMemoryType
x) (Int
4))
{-# LINE 2167 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

        {-# INLINE readField #-}
        readField :: Ptr VkMemoryType -> IO (FieldType "heapIndex" VkMemoryType)
readField Ptr VkMemoryType
p
          = Ptr VkMemoryType -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMemoryType
p (Int
4)
{-# LINE 2171 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance {-# OVERLAPPING #-} CanWriteField "heapIndex" VkMemoryType
         where
        {-# INLINE writeField #-}
        writeField :: Ptr VkMemoryType -> FieldType "heapIndex" VkMemoryType -> IO ()
writeField Ptr VkMemoryType
p
          = Ptr VkMemoryType -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMemoryType
p (Int
4)
{-# LINE 2177 "src-gen/Graphics/Vulkan/Types/Struct/Memory.hsc" #-}

instance Show VkMemoryType where
        showsPrec :: Int -> VkMemoryType -> ShowS
showsPrec Int
d VkMemoryType
x
          = String -> ShowS
showString String
"VkMemoryType {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
              String -> ShowS
showString String
"propertyFlags = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                Int -> VkMemoryPropertyFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMemoryType -> FieldType "propertyFlags" VkMemoryType
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"propertyFlags" VkMemoryType
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
"heapIndex = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                      Int -> Word32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMemoryType -> FieldType "heapIndex" VkMemoryType
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"heapIndex" VkMemoryType
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'