{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Vulkan.Types.Struct.DedicatedAllocation
(VkDedicatedAllocationBufferCreateInfoNV(..),
VkDedicatedAllocationImageCreateInfoNV(..),
VkDedicatedAllocationMemoryAllocateInfoNV(..))
where
import Foreign.Storable (Storable (..))
import GHC.Base (Addr#, ByteArray#,
byteArrayContents#,
plusAddr#)
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.BaseTypes (VkBool32)
import Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import Graphics.Vulkan.Types.Handles (VkBuffer, VkImage)
import Graphics.Vulkan.Types.Struct.Buffer (VkBufferCreateInfo)
import Graphics.Vulkan.Types.Struct.Image (VkImageCreateInfo)
import Graphics.Vulkan.Types.Struct.Memory (VkMemoryAllocateInfo)
import System.IO.Unsafe (unsafeDupablePerformIO)
data VkDedicatedAllocationBufferCreateInfoNV = VkDedicatedAllocationBufferCreateInfoNV# Addr#
ByteArray#
instance Eq VkDedicatedAllocationBufferCreateInfoNV where
(VkDedicatedAllocationBufferCreateInfoNV# Addr#
a ByteArray#
_) == :: VkDedicatedAllocationBufferCreateInfoNV
-> VkDedicatedAllocationBufferCreateInfoNV -> Bool
==
x :: VkDedicatedAllocationBufferCreateInfoNV
x@(VkDedicatedAllocationBufferCreateInfoNV# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkDedicatedAllocationBufferCreateInfoNV -> Int
forall a. Storable a => a -> Int
sizeOf VkDedicatedAllocationBufferCreateInfoNV
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkDedicatedAllocationBufferCreateInfoNV where
(VkDedicatedAllocationBufferCreateInfoNV# Addr#
a ByteArray#
_) compare :: VkDedicatedAllocationBufferCreateInfoNV
-> VkDedicatedAllocationBufferCreateInfoNV -> Ordering
`compare`
x :: VkDedicatedAllocationBufferCreateInfoNV
x@(VkDedicatedAllocationBufferCreateInfoNV# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkDedicatedAllocationBufferCreateInfoNV -> Int
forall a. Storable a => a -> Int
sizeOf VkDedicatedAllocationBufferCreateInfoNV
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkDedicatedAllocationBufferCreateInfoNV where
sizeOf :: VkDedicatedAllocationBufferCreateInfoNV -> Int
sizeOf ~VkDedicatedAllocationBufferCreateInfoNV
_
= (Int
24)
{-# LINE 56 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkDedicatedAllocationBufferCreateInfoNV -> Int
alignment ~VkDedicatedAllocationBufferCreateInfoNV
_
= Int
8
{-# LINE 60 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkDedicatedAllocationBufferCreateInfoNV
-> IO VkDedicatedAllocationBufferCreateInfoNV
peek = Ptr VkDedicatedAllocationBufferCreateInfoNV
-> IO VkDedicatedAllocationBufferCreateInfoNV
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkDedicatedAllocationBufferCreateInfoNV
-> VkDedicatedAllocationBufferCreateInfoNV -> IO ()
poke = Ptr VkDedicatedAllocationBufferCreateInfoNV
-> VkDedicatedAllocationBufferCreateInfoNV -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkDedicatedAllocationBufferCreateInfoNV
where
unsafeAddr :: VkDedicatedAllocationBufferCreateInfoNV -> Addr#
unsafeAddr (VkDedicatedAllocationBufferCreateInfoNV# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkDedicatedAllocationBufferCreateInfoNV -> ByteArray#
unsafeByteArray (VkDedicatedAllocationBufferCreateInfoNV# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkDedicatedAllocationBufferCreateInfoNV
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkDedicatedAllocationBufferCreateInfoNV
VkDedicatedAllocationBufferCreateInfoNV#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkDedicatedAllocationBufferCreateInfoNV
where
type StructFields VkDedicatedAllocationBufferCreateInfoNV =
'["sType", "pNext", "dedicatedAllocation"]
type CUnionType VkDedicatedAllocationBufferCreateInfoNV = 'False
type ReturnedOnly VkDedicatedAllocationBufferCreateInfoNV = 'False
type StructExtends VkDedicatedAllocationBufferCreateInfoNV =
'[VkBufferCreateInfo]
instance {-# OVERLAPPING #-}
HasField "sType" VkDedicatedAllocationBufferCreateInfoNV where
type FieldType "sType" VkDedicatedAllocationBufferCreateInfoNV =
VkStructureType
type FieldOptional "sType" VkDedicatedAllocationBufferCreateInfoNV
= 'False
type FieldOffset "sType" VkDedicatedAllocationBufferCreateInfoNV =
(0)
{-# LINE 101 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "sType" VkDedicatedAllocationBufferCreateInfoNV =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 110 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkDedicatedAllocationBufferCreateInfoNV where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationBufferCreateInfoNV
-> FieldType "sType" VkDedicatedAllocationBufferCreateInfoNV
getField VkDedicatedAllocationBufferCreateInfoNV
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationBufferCreateInfoNV
-> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationBufferCreateInfoNV
-> Ptr VkDedicatedAllocationBufferCreateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationBufferCreateInfoNV
x) (Int
0))
{-# LINE 117 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationBufferCreateInfoNV
-> IO (FieldType "sType" VkDedicatedAllocationBufferCreateInfoNV)
readField Ptr VkDedicatedAllocationBufferCreateInfoNV
p
= Ptr VkDedicatedAllocationBufferCreateInfoNV
-> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationBufferCreateInfoNV
p (Int
0)
{-# LINE 121 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkDedicatedAllocationBufferCreateInfoNV where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationBufferCreateInfoNV
-> FieldType "sType" VkDedicatedAllocationBufferCreateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationBufferCreateInfoNV
p
= Ptr VkDedicatedAllocationBufferCreateInfoNV
-> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationBufferCreateInfoNV
p (Int
0)
{-# LINE 127 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkDedicatedAllocationBufferCreateInfoNV where
type FieldType "pNext" VkDedicatedAllocationBufferCreateInfoNV =
Ptr Void
type FieldOptional "pNext" VkDedicatedAllocationBufferCreateInfoNV
= 'False
type FieldOffset "pNext" VkDedicatedAllocationBufferCreateInfoNV =
(8)
{-# LINE 136 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "pNext" VkDedicatedAllocationBufferCreateInfoNV =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 145 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkDedicatedAllocationBufferCreateInfoNV where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationBufferCreateInfoNV
-> FieldType "pNext" VkDedicatedAllocationBufferCreateInfoNV
getField VkDedicatedAllocationBufferCreateInfoNV
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationBufferCreateInfoNV -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationBufferCreateInfoNV
-> Ptr VkDedicatedAllocationBufferCreateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationBufferCreateInfoNV
x) (Int
8))
{-# LINE 152 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationBufferCreateInfoNV
-> IO (FieldType "pNext" VkDedicatedAllocationBufferCreateInfoNV)
readField Ptr VkDedicatedAllocationBufferCreateInfoNV
p
= Ptr VkDedicatedAllocationBufferCreateInfoNV -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationBufferCreateInfoNV
p (Int
8)
{-# LINE 156 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkDedicatedAllocationBufferCreateInfoNV where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationBufferCreateInfoNV
-> FieldType "pNext" VkDedicatedAllocationBufferCreateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationBufferCreateInfoNV
p
= Ptr VkDedicatedAllocationBufferCreateInfoNV
-> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationBufferCreateInfoNV
p (Int
8)
{-# LINE 162 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "dedicatedAllocation"
VkDedicatedAllocationBufferCreateInfoNV
where
type FieldType "dedicatedAllocation"
VkDedicatedAllocationBufferCreateInfoNV
= VkBool32
type FieldOptional "dedicatedAllocation"
VkDedicatedAllocationBufferCreateInfoNV
= 'False
type FieldOffset "dedicatedAllocation"
VkDedicatedAllocationBufferCreateInfoNV
=
(16)
{-# LINE 177 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "dedicatedAllocation"
VkDedicatedAllocationBufferCreateInfoNV
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 187 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "dedicatedAllocation"
VkDedicatedAllocationBufferCreateInfoNV
where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationBufferCreateInfoNV
-> FieldType
"dedicatedAllocation" VkDedicatedAllocationBufferCreateInfoNV
getField VkDedicatedAllocationBufferCreateInfoNV
x
= IO VkBool32 -> VkBool32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationBufferCreateInfoNV -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationBufferCreateInfoNV
-> Ptr VkDedicatedAllocationBufferCreateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationBufferCreateInfoNV
x) (Int
16))
{-# LINE 196 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationBufferCreateInfoNV
-> IO
(FieldType
"dedicatedAllocation" VkDedicatedAllocationBufferCreateInfoNV)
readField Ptr VkDedicatedAllocationBufferCreateInfoNV
p
= Ptr VkDedicatedAllocationBufferCreateInfoNV -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationBufferCreateInfoNV
p (Int
16)
{-# LINE 200 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "dedicatedAllocation"
VkDedicatedAllocationBufferCreateInfoNV
where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationBufferCreateInfoNV
-> FieldType
"dedicatedAllocation" VkDedicatedAllocationBufferCreateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationBufferCreateInfoNV
p
= Ptr VkDedicatedAllocationBufferCreateInfoNV
-> Int -> VkBool32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationBufferCreateInfoNV
p (Int
16)
{-# LINE 208 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance Show VkDedicatedAllocationBufferCreateInfoNV where
showsPrec :: Int -> VkDedicatedAllocationBufferCreateInfoNV -> ShowS
showsPrec Int
d VkDedicatedAllocationBufferCreateInfoNV
x
= String -> ShowS
showString String
"VkDedicatedAllocationBufferCreateInfoNV {" 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 (VkDedicatedAllocationBufferCreateInfoNV
-> FieldType "sType" VkDedicatedAllocationBufferCreateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkDedicatedAllocationBufferCreateInfoNV
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 (VkDedicatedAllocationBufferCreateInfoNV
-> FieldType "pNext" VkDedicatedAllocationBufferCreateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkDedicatedAllocationBufferCreateInfoNV
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
"dedicatedAllocation = " 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 (VkDedicatedAllocationBufferCreateInfoNV
-> FieldType
"dedicatedAllocation" VkDedicatedAllocationBufferCreateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"dedicatedAllocation" VkDedicatedAllocationBufferCreateInfoNV
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkDedicatedAllocationImageCreateInfoNV = VkDedicatedAllocationImageCreateInfoNV# Addr#
ByteArray#
instance Eq VkDedicatedAllocationImageCreateInfoNV where
(VkDedicatedAllocationImageCreateInfoNV# Addr#
a ByteArray#
_) == :: VkDedicatedAllocationImageCreateInfoNV
-> VkDedicatedAllocationImageCreateInfoNV -> Bool
==
x :: VkDedicatedAllocationImageCreateInfoNV
x@(VkDedicatedAllocationImageCreateInfoNV# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkDedicatedAllocationImageCreateInfoNV -> Int
forall a. Storable a => a -> Int
sizeOf VkDedicatedAllocationImageCreateInfoNV
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkDedicatedAllocationImageCreateInfoNV where
(VkDedicatedAllocationImageCreateInfoNV# Addr#
a ByteArray#
_) compare :: VkDedicatedAllocationImageCreateInfoNV
-> VkDedicatedAllocationImageCreateInfoNV -> Ordering
`compare`
x :: VkDedicatedAllocationImageCreateInfoNV
x@(VkDedicatedAllocationImageCreateInfoNV# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkDedicatedAllocationImageCreateInfoNV -> Int
forall a. Storable a => a -> Int
sizeOf VkDedicatedAllocationImageCreateInfoNV
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkDedicatedAllocationImageCreateInfoNV where
sizeOf :: VkDedicatedAllocationImageCreateInfoNV -> Int
sizeOf ~VkDedicatedAllocationImageCreateInfoNV
_
= (Int
24)
{-# LINE 248 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkDedicatedAllocationImageCreateInfoNV -> Int
alignment ~VkDedicatedAllocationImageCreateInfoNV
_
= Int
8
{-# LINE 252 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkDedicatedAllocationImageCreateInfoNV
-> IO VkDedicatedAllocationImageCreateInfoNV
peek = Ptr VkDedicatedAllocationImageCreateInfoNV
-> IO VkDedicatedAllocationImageCreateInfoNV
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkDedicatedAllocationImageCreateInfoNV
-> VkDedicatedAllocationImageCreateInfoNV -> IO ()
poke = Ptr VkDedicatedAllocationImageCreateInfoNV
-> VkDedicatedAllocationImageCreateInfoNV -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkDedicatedAllocationImageCreateInfoNV
where
unsafeAddr :: VkDedicatedAllocationImageCreateInfoNV -> Addr#
unsafeAddr (VkDedicatedAllocationImageCreateInfoNV# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkDedicatedAllocationImageCreateInfoNV -> ByteArray#
unsafeByteArray (VkDedicatedAllocationImageCreateInfoNV# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkDedicatedAllocationImageCreateInfoNV
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkDedicatedAllocationImageCreateInfoNV
VkDedicatedAllocationImageCreateInfoNV#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkDedicatedAllocationImageCreateInfoNV where
type StructFields VkDedicatedAllocationImageCreateInfoNV =
'["sType", "pNext", "dedicatedAllocation"]
type CUnionType VkDedicatedAllocationImageCreateInfoNV = 'False
type ReturnedOnly VkDedicatedAllocationImageCreateInfoNV = 'False
type StructExtends VkDedicatedAllocationImageCreateInfoNV =
'[VkImageCreateInfo]
instance {-# OVERLAPPING #-}
HasField "sType" VkDedicatedAllocationImageCreateInfoNV where
type FieldType "sType" VkDedicatedAllocationImageCreateInfoNV =
VkStructureType
type FieldOptional "sType" VkDedicatedAllocationImageCreateInfoNV =
'False
type FieldOffset "sType" VkDedicatedAllocationImageCreateInfoNV =
(0)
{-# LINE 292 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "sType" VkDedicatedAllocationImageCreateInfoNV =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 301 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkDedicatedAllocationImageCreateInfoNV where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationImageCreateInfoNV
-> FieldType "sType" VkDedicatedAllocationImageCreateInfoNV
getField VkDedicatedAllocationImageCreateInfoNV
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationImageCreateInfoNV
-> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationImageCreateInfoNV
-> Ptr VkDedicatedAllocationImageCreateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationImageCreateInfoNV
x) (Int
0))
{-# LINE 308 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationImageCreateInfoNV
-> IO (FieldType "sType" VkDedicatedAllocationImageCreateInfoNV)
readField Ptr VkDedicatedAllocationImageCreateInfoNV
p
= Ptr VkDedicatedAllocationImageCreateInfoNV
-> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationImageCreateInfoNV
p (Int
0)
{-# LINE 312 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkDedicatedAllocationImageCreateInfoNV where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationImageCreateInfoNV
-> FieldType "sType" VkDedicatedAllocationImageCreateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationImageCreateInfoNV
p
= Ptr VkDedicatedAllocationImageCreateInfoNV
-> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationImageCreateInfoNV
p (Int
0)
{-# LINE 318 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkDedicatedAllocationImageCreateInfoNV where
type FieldType "pNext" VkDedicatedAllocationImageCreateInfoNV =
Ptr Void
type FieldOptional "pNext" VkDedicatedAllocationImageCreateInfoNV =
'False
type FieldOffset "pNext" VkDedicatedAllocationImageCreateInfoNV =
(8)
{-# LINE 327 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "pNext" VkDedicatedAllocationImageCreateInfoNV =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 336 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkDedicatedAllocationImageCreateInfoNV where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationImageCreateInfoNV
-> FieldType "pNext" VkDedicatedAllocationImageCreateInfoNV
getField VkDedicatedAllocationImageCreateInfoNV
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationImageCreateInfoNV -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationImageCreateInfoNV
-> Ptr VkDedicatedAllocationImageCreateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationImageCreateInfoNV
x) (Int
8))
{-# LINE 343 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationImageCreateInfoNV
-> IO (FieldType "pNext" VkDedicatedAllocationImageCreateInfoNV)
readField Ptr VkDedicatedAllocationImageCreateInfoNV
p
= Ptr VkDedicatedAllocationImageCreateInfoNV -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationImageCreateInfoNV
p (Int
8)
{-# LINE 347 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkDedicatedAllocationImageCreateInfoNV where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationImageCreateInfoNV
-> FieldType "pNext" VkDedicatedAllocationImageCreateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationImageCreateInfoNV
p
= Ptr VkDedicatedAllocationImageCreateInfoNV
-> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationImageCreateInfoNV
p (Int
8)
{-# LINE 353 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "dedicatedAllocation"
VkDedicatedAllocationImageCreateInfoNV
where
type FieldType "dedicatedAllocation"
VkDedicatedAllocationImageCreateInfoNV
= VkBool32
type FieldOptional "dedicatedAllocation"
VkDedicatedAllocationImageCreateInfoNV
= 'False
type FieldOffset "dedicatedAllocation"
VkDedicatedAllocationImageCreateInfoNV
=
(16)
{-# LINE 368 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "dedicatedAllocation"
VkDedicatedAllocationImageCreateInfoNV
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 378 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "dedicatedAllocation"
VkDedicatedAllocationImageCreateInfoNV
where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationImageCreateInfoNV
-> FieldType
"dedicatedAllocation" VkDedicatedAllocationImageCreateInfoNV
getField VkDedicatedAllocationImageCreateInfoNV
x
= IO VkBool32 -> VkBool32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationImageCreateInfoNV -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationImageCreateInfoNV
-> Ptr VkDedicatedAllocationImageCreateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationImageCreateInfoNV
x) (Int
16))
{-# LINE 387 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationImageCreateInfoNV
-> IO
(FieldType
"dedicatedAllocation" VkDedicatedAllocationImageCreateInfoNV)
readField Ptr VkDedicatedAllocationImageCreateInfoNV
p
= Ptr VkDedicatedAllocationImageCreateInfoNV -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationImageCreateInfoNV
p (Int
16)
{-# LINE 391 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "dedicatedAllocation"
VkDedicatedAllocationImageCreateInfoNV
where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationImageCreateInfoNV
-> FieldType
"dedicatedAllocation" VkDedicatedAllocationImageCreateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationImageCreateInfoNV
p
= Ptr VkDedicatedAllocationImageCreateInfoNV
-> Int -> VkBool32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationImageCreateInfoNV
p (Int
16)
{-# LINE 399 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance Show VkDedicatedAllocationImageCreateInfoNV where
showsPrec :: Int -> VkDedicatedAllocationImageCreateInfoNV -> ShowS
showsPrec Int
d VkDedicatedAllocationImageCreateInfoNV
x
= String -> ShowS
showString String
"VkDedicatedAllocationImageCreateInfoNV {" 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 (VkDedicatedAllocationImageCreateInfoNV
-> FieldType "sType" VkDedicatedAllocationImageCreateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkDedicatedAllocationImageCreateInfoNV
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 (VkDedicatedAllocationImageCreateInfoNV
-> FieldType "pNext" VkDedicatedAllocationImageCreateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkDedicatedAllocationImageCreateInfoNV
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
"dedicatedAllocation = " 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 (VkDedicatedAllocationImageCreateInfoNV
-> FieldType
"dedicatedAllocation" VkDedicatedAllocationImageCreateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"dedicatedAllocation" VkDedicatedAllocationImageCreateInfoNV
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkDedicatedAllocationMemoryAllocateInfoNV = VkDedicatedAllocationMemoryAllocateInfoNV# Addr#
ByteArray#
instance Eq VkDedicatedAllocationMemoryAllocateInfoNV where
(VkDedicatedAllocationMemoryAllocateInfoNV# Addr#
a ByteArray#
_) == :: VkDedicatedAllocationMemoryAllocateInfoNV
-> VkDedicatedAllocationMemoryAllocateInfoNV -> Bool
==
x :: VkDedicatedAllocationMemoryAllocateInfoNV
x@(VkDedicatedAllocationMemoryAllocateInfoNV# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkDedicatedAllocationMemoryAllocateInfoNV -> Int
forall a. Storable a => a -> Int
sizeOf VkDedicatedAllocationMemoryAllocateInfoNV
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkDedicatedAllocationMemoryAllocateInfoNV where
(VkDedicatedAllocationMemoryAllocateInfoNV# Addr#
a ByteArray#
_) compare :: VkDedicatedAllocationMemoryAllocateInfoNV
-> VkDedicatedAllocationMemoryAllocateInfoNV -> Ordering
`compare`
x :: VkDedicatedAllocationMemoryAllocateInfoNV
x@(VkDedicatedAllocationMemoryAllocateInfoNV# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkDedicatedAllocationMemoryAllocateInfoNV -> Int
forall a. Storable a => a -> Int
sizeOf VkDedicatedAllocationMemoryAllocateInfoNV
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkDedicatedAllocationMemoryAllocateInfoNV where
sizeOf :: VkDedicatedAllocationMemoryAllocateInfoNV -> Int
sizeOf ~VkDedicatedAllocationMemoryAllocateInfoNV
_
= (Int
32)
{-# LINE 440 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkDedicatedAllocationMemoryAllocateInfoNV -> Int
alignment ~VkDedicatedAllocationMemoryAllocateInfoNV
_
= Int
8
{-# LINE 444 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> IO VkDedicatedAllocationMemoryAllocateInfoNV
peek = Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> IO VkDedicatedAllocationMemoryAllocateInfoNV
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> VkDedicatedAllocationMemoryAllocateInfoNV -> IO ()
poke = Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> VkDedicatedAllocationMemoryAllocateInfoNV -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim
VkDedicatedAllocationMemoryAllocateInfoNV
where
unsafeAddr :: VkDedicatedAllocationMemoryAllocateInfoNV -> Addr#
unsafeAddr (VkDedicatedAllocationMemoryAllocateInfoNV# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkDedicatedAllocationMemoryAllocateInfoNV -> ByteArray#
unsafeByteArray (VkDedicatedAllocationMemoryAllocateInfoNV# Addr#
_ ByteArray#
b)
= ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkDedicatedAllocationMemoryAllocateInfoNV
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkDedicatedAllocationMemoryAllocateInfoNV
VkDedicatedAllocationMemoryAllocateInfoNV#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkDedicatedAllocationMemoryAllocateInfoNV
where
type StructFields VkDedicatedAllocationMemoryAllocateInfoNV =
'["sType", "pNext", "image", "buffer"]
type CUnionType VkDedicatedAllocationMemoryAllocateInfoNV = 'False
type ReturnedOnly VkDedicatedAllocationMemoryAllocateInfoNV =
'False
type StructExtends VkDedicatedAllocationMemoryAllocateInfoNV =
'[VkMemoryAllocateInfo]
instance {-# OVERLAPPING #-}
HasField "sType" VkDedicatedAllocationMemoryAllocateInfoNV where
type FieldType "sType" VkDedicatedAllocationMemoryAllocateInfoNV =
VkStructureType
type FieldOptional "sType"
VkDedicatedAllocationMemoryAllocateInfoNV
= 'False
type FieldOffset "sType" VkDedicatedAllocationMemoryAllocateInfoNV
=
(0)
{-# LINE 490 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "sType" VkDedicatedAllocationMemoryAllocateInfoNV
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 499 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkDedicatedAllocationMemoryAllocateInfoNV
where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "sType" VkDedicatedAllocationMemoryAllocateInfoNV
getField VkDedicatedAllocationMemoryAllocateInfoNV
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationMemoryAllocateInfoNV
-> Ptr VkDedicatedAllocationMemoryAllocateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationMemoryAllocateInfoNV
x) (Int
0))
{-# LINE 507 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> IO (FieldType "sType" VkDedicatedAllocationMemoryAllocateInfoNV)
readField Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p
= Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p (Int
0)
{-# LINE 511 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkDedicatedAllocationMemoryAllocateInfoNV
where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "sType" VkDedicatedAllocationMemoryAllocateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p
= Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p (Int
0)
{-# LINE 518 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkDedicatedAllocationMemoryAllocateInfoNV where
type FieldType "pNext" VkDedicatedAllocationMemoryAllocateInfoNV =
Ptr Void
type FieldOptional "pNext"
VkDedicatedAllocationMemoryAllocateInfoNV
= 'False
type FieldOffset "pNext" VkDedicatedAllocationMemoryAllocateInfoNV
=
(8)
{-# LINE 529 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "pNext" VkDedicatedAllocationMemoryAllocateInfoNV
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 538 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkDedicatedAllocationMemoryAllocateInfoNV
where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "pNext" VkDedicatedAllocationMemoryAllocateInfoNV
getField VkDedicatedAllocationMemoryAllocateInfoNV
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationMemoryAllocateInfoNV
-> Ptr VkDedicatedAllocationMemoryAllocateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationMemoryAllocateInfoNV
x) (Int
8))
{-# LINE 546 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> IO (FieldType "pNext" VkDedicatedAllocationMemoryAllocateInfoNV)
readField Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p
= Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p (Int
8)
{-# LINE 550 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkDedicatedAllocationMemoryAllocateInfoNV
where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "pNext" VkDedicatedAllocationMemoryAllocateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p
= Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p (Int
8)
{-# LINE 557 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "image" VkDedicatedAllocationMemoryAllocateInfoNV where
type FieldType "image" VkDedicatedAllocationMemoryAllocateInfoNV =
VkImage
type FieldOptional "image"
VkDedicatedAllocationMemoryAllocateInfoNV
= 'True
type FieldOffset "image" VkDedicatedAllocationMemoryAllocateInfoNV
=
(16)
{-# LINE 568 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "image" VkDedicatedAllocationMemoryAllocateInfoNV
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 577 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "image" VkDedicatedAllocationMemoryAllocateInfoNV
where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "image" VkDedicatedAllocationMemoryAllocateInfoNV
getField VkDedicatedAllocationMemoryAllocateInfoNV
x
= IO VkImage -> VkImage
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationMemoryAllocateInfoNV -> Int -> IO VkImage
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationMemoryAllocateInfoNV
-> Ptr VkDedicatedAllocationMemoryAllocateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationMemoryAllocateInfoNV
x) (Int
16))
{-# LINE 585 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> IO (FieldType "image" VkDedicatedAllocationMemoryAllocateInfoNV)
readField Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p
= Ptr VkDedicatedAllocationMemoryAllocateInfoNV -> Int -> IO VkImage
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p (Int
16)
{-# LINE 589 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "image" VkDedicatedAllocationMemoryAllocateInfoNV
where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "image" VkDedicatedAllocationMemoryAllocateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p
= Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> Int -> VkImage -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p (Int
16)
{-# LINE 596 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "buffer" VkDedicatedAllocationMemoryAllocateInfoNV where
type FieldType "buffer" VkDedicatedAllocationMemoryAllocateInfoNV =
VkBuffer
type FieldOptional "buffer"
VkDedicatedAllocationMemoryAllocateInfoNV
= 'True
type FieldOffset "buffer" VkDedicatedAllocationMemoryAllocateInfoNV
=
(24)
{-# LINE 607 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
type FieldIsArray "buffer"
VkDedicatedAllocationMemoryAllocateInfoNV
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
24)
{-# LINE 617 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "buffer" VkDedicatedAllocationMemoryAllocateInfoNV
where
{-# NOINLINE getField #-}
getField :: VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "buffer" VkDedicatedAllocationMemoryAllocateInfoNV
getField VkDedicatedAllocationMemoryAllocateInfoNV
x
= IO VkBuffer -> VkBuffer
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkDedicatedAllocationMemoryAllocateInfoNV -> Int -> IO VkBuffer
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkDedicatedAllocationMemoryAllocateInfoNV
-> Ptr VkDedicatedAllocationMemoryAllocateInfoNV
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkDedicatedAllocationMemoryAllocateInfoNV
x) (Int
24))
{-# LINE 625 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> IO
(FieldType "buffer" VkDedicatedAllocationMemoryAllocateInfoNV)
readField Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p
= Ptr VkDedicatedAllocationMemoryAllocateInfoNV -> Int -> IO VkBuffer
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p (Int
24)
{-# LINE 629 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "buffer" VkDedicatedAllocationMemoryAllocateInfoNV
where
{-# INLINE writeField #-}
writeField :: Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "buffer" VkDedicatedAllocationMemoryAllocateInfoNV
-> IO ()
writeField Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p
= Ptr VkDedicatedAllocationMemoryAllocateInfoNV
-> Int -> VkBuffer -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkDedicatedAllocationMemoryAllocateInfoNV
p (Int
24)
{-# LINE 636 "src-gen/Graphics/Vulkan/Types/Struct/DedicatedAllocation.hsc" #-}
instance Show VkDedicatedAllocationMemoryAllocateInfoNV where
showsPrec :: Int -> VkDedicatedAllocationMemoryAllocateInfoNV -> ShowS
showsPrec Int
d VkDedicatedAllocationMemoryAllocateInfoNV
x
= String -> ShowS
showString String
"VkDedicatedAllocationMemoryAllocateInfoNV {" 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 (VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "sType" VkDedicatedAllocationMemoryAllocateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkDedicatedAllocationMemoryAllocateInfoNV
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 (VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "pNext" VkDedicatedAllocationMemoryAllocateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkDedicatedAllocationMemoryAllocateInfoNV
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 (VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "image" VkDedicatedAllocationMemoryAllocateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"image" VkDedicatedAllocationMemoryAllocateInfoNV
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 (VkDedicatedAllocationMemoryAllocateInfoNV
-> FieldType "buffer" VkDedicatedAllocationMemoryAllocateInfoNV
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"buffer" VkDedicatedAllocationMemoryAllocateInfoNV
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'