{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Vulkan.Types.Struct.Sparse
(VkSparseBufferMemoryBindInfo(..),
VkSparseImageFormatProperties(..),
VkSparseImageFormatProperties2(..),
VkSparseImageFormatProperties2KHR, VkSparseImageMemoryBind(..),
VkSparseImageMemoryBindInfo(..),
VkSparseImageMemoryRequirements(..),
VkSparseImageMemoryRequirements2(..),
VkSparseImageMemoryRequirements2KHR,
VkSparseImageOpaqueMemoryBindInfo(..), VkSparseMemoryBind(..))
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 (VkDeviceSize)
import Graphics.Vulkan.Types.Enum.Image (VkImageAspectFlags)
import Graphics.Vulkan.Types.Enum.Sparse (VkSparseImageFormatFlags,
VkSparseMemoryBindFlags)
import Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import Graphics.Vulkan.Types.Handles (VkBuffer,
VkDeviceMemory,
VkImage)
import Graphics.Vulkan.Types.Struct.Extent (VkExtent3D)
import Graphics.Vulkan.Types.Struct.Image (VkImageSubresource)
import Graphics.Vulkan.Types.Struct.Offset (VkOffset3D)
import System.IO.Unsafe (unsafeDupablePerformIO)
data VkSparseBufferMemoryBindInfo = VkSparseBufferMemoryBindInfo# Addr#
ByteArray#
instance Eq VkSparseBufferMemoryBindInfo where
(VkSparseBufferMemoryBindInfo# Addr#
a ByteArray#
_) == :: VkSparseBufferMemoryBindInfo
-> VkSparseBufferMemoryBindInfo -> Bool
==
x :: VkSparseBufferMemoryBindInfo
x@(VkSparseBufferMemoryBindInfo# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseBufferMemoryBindInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseBufferMemoryBindInfo
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSparseBufferMemoryBindInfo where
(VkSparseBufferMemoryBindInfo# Addr#
a ByteArray#
_) compare :: VkSparseBufferMemoryBindInfo
-> VkSparseBufferMemoryBindInfo -> Ordering
`compare`
x :: VkSparseBufferMemoryBindInfo
x@(VkSparseBufferMemoryBindInfo# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseBufferMemoryBindInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseBufferMemoryBindInfo
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSparseBufferMemoryBindInfo where
sizeOf :: VkSparseBufferMemoryBindInfo -> Int
sizeOf ~VkSparseBufferMemoryBindInfo
_ = (Int
24)
{-# LINE 65 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSparseBufferMemoryBindInfo -> Int
alignment ~VkSparseBufferMemoryBindInfo
_
= Int
8
{-# LINE 69 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSparseBufferMemoryBindInfo -> IO VkSparseBufferMemoryBindInfo
peek = Ptr VkSparseBufferMemoryBindInfo -> IO VkSparseBufferMemoryBindInfo
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSparseBufferMemoryBindInfo
-> VkSparseBufferMemoryBindInfo -> IO ()
poke = Ptr VkSparseBufferMemoryBindInfo
-> VkSparseBufferMemoryBindInfo -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSparseBufferMemoryBindInfo where
unsafeAddr :: VkSparseBufferMemoryBindInfo -> Addr#
unsafeAddr (VkSparseBufferMemoryBindInfo# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSparseBufferMemoryBindInfo -> ByteArray#
unsafeByteArray (VkSparseBufferMemoryBindInfo# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSparseBufferMemoryBindInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSparseBufferMemoryBindInfo
VkSparseBufferMemoryBindInfo#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSparseBufferMemoryBindInfo where
type StructFields VkSparseBufferMemoryBindInfo =
'["buffer", "bindCount", "pBinds"]
type CUnionType VkSparseBufferMemoryBindInfo = 'False
type ReturnedOnly VkSparseBufferMemoryBindInfo = 'False
type StructExtends VkSparseBufferMemoryBindInfo = '[]
instance {-# OVERLAPPING #-}
HasField "buffer" VkSparseBufferMemoryBindInfo where
type FieldType "buffer" VkSparseBufferMemoryBindInfo = VkBuffer
type FieldOptional "buffer" VkSparseBufferMemoryBindInfo = 'False
type FieldOffset "buffer" VkSparseBufferMemoryBindInfo =
(0)
{-# LINE 105 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "buffer" VkSparseBufferMemoryBindInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 113 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "buffer" VkSparseBufferMemoryBindInfo where
{-# NOINLINE getField #-}
getField :: VkSparseBufferMemoryBindInfo
-> FieldType "buffer" VkSparseBufferMemoryBindInfo
getField VkSparseBufferMemoryBindInfo
x
= IO VkBuffer -> VkBuffer
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseBufferMemoryBindInfo -> Int -> IO VkBuffer
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseBufferMemoryBindInfo -> Ptr VkSparseBufferMemoryBindInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseBufferMemoryBindInfo
x) (Int
0))
{-# LINE 120 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseBufferMemoryBindInfo
-> IO (FieldType "buffer" VkSparseBufferMemoryBindInfo)
readField Ptr VkSparseBufferMemoryBindInfo
p
= Ptr VkSparseBufferMemoryBindInfo -> Int -> IO VkBuffer
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseBufferMemoryBindInfo
p (Int
0)
{-# LINE 124 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "buffer" VkSparseBufferMemoryBindInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseBufferMemoryBindInfo
-> FieldType "buffer" VkSparseBufferMemoryBindInfo -> IO ()
writeField Ptr VkSparseBufferMemoryBindInfo
p
= Ptr VkSparseBufferMemoryBindInfo -> Int -> VkBuffer -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseBufferMemoryBindInfo
p (Int
0)
{-# LINE 130 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "bindCount" VkSparseBufferMemoryBindInfo where
type FieldType "bindCount" VkSparseBufferMemoryBindInfo = Word32
type FieldOptional "bindCount" VkSparseBufferMemoryBindInfo =
'False
type FieldOffset "bindCount" VkSparseBufferMemoryBindInfo =
(8)
{-# LINE 138 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "bindCount" VkSparseBufferMemoryBindInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 146 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "bindCount" VkSparseBufferMemoryBindInfo where
{-# NOINLINE getField #-}
getField :: VkSparseBufferMemoryBindInfo
-> FieldType "bindCount" VkSparseBufferMemoryBindInfo
getField VkSparseBufferMemoryBindInfo
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseBufferMemoryBindInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseBufferMemoryBindInfo -> Ptr VkSparseBufferMemoryBindInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseBufferMemoryBindInfo
x) (Int
8))
{-# LINE 153 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseBufferMemoryBindInfo
-> IO (FieldType "bindCount" VkSparseBufferMemoryBindInfo)
readField Ptr VkSparseBufferMemoryBindInfo
p
= Ptr VkSparseBufferMemoryBindInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseBufferMemoryBindInfo
p (Int
8)
{-# LINE 157 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "bindCount" VkSparseBufferMemoryBindInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseBufferMemoryBindInfo
-> FieldType "bindCount" VkSparseBufferMemoryBindInfo -> IO ()
writeField Ptr VkSparseBufferMemoryBindInfo
p
= Ptr VkSparseBufferMemoryBindInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseBufferMemoryBindInfo
p (Int
8)
{-# LINE 163 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pBinds" VkSparseBufferMemoryBindInfo where
type FieldType "pBinds" VkSparseBufferMemoryBindInfo =
Ptr VkSparseMemoryBind
type FieldOptional "pBinds" VkSparseBufferMemoryBindInfo = 'False
type FieldOffset "pBinds" VkSparseBufferMemoryBindInfo =
(16)
{-# LINE 171 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "pBinds" VkSparseBufferMemoryBindInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 179 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pBinds" VkSparseBufferMemoryBindInfo where
{-# NOINLINE getField #-}
getField :: VkSparseBufferMemoryBindInfo
-> FieldType "pBinds" VkSparseBufferMemoryBindInfo
getField VkSparseBufferMemoryBindInfo
x
= IO (Ptr VkSparseMemoryBind) -> Ptr VkSparseMemoryBind
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseBufferMemoryBindInfo
-> Int -> IO (Ptr VkSparseMemoryBind)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseBufferMemoryBindInfo -> Ptr VkSparseBufferMemoryBindInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseBufferMemoryBindInfo
x) (Int
16))
{-# LINE 186 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseBufferMemoryBindInfo
-> IO (FieldType "pBinds" VkSparseBufferMemoryBindInfo)
readField Ptr VkSparseBufferMemoryBindInfo
p
= Ptr VkSparseBufferMemoryBindInfo
-> Int -> IO (Ptr VkSparseMemoryBind)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseBufferMemoryBindInfo
p (Int
16)
{-# LINE 190 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pBinds" VkSparseBufferMemoryBindInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseBufferMemoryBindInfo
-> FieldType "pBinds" VkSparseBufferMemoryBindInfo -> IO ()
writeField Ptr VkSparseBufferMemoryBindInfo
p
= Ptr VkSparseBufferMemoryBindInfo
-> Int -> Ptr VkSparseMemoryBind -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseBufferMemoryBindInfo
p (Int
16)
{-# LINE 196 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance Show VkSparseBufferMemoryBindInfo where
showsPrec :: Int -> VkSparseBufferMemoryBindInfo -> ShowS
showsPrec Int
d VkSparseBufferMemoryBindInfo
x
= String -> ShowS
showString String
"VkSparseBufferMemoryBindInfo {" 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 (VkSparseBufferMemoryBindInfo
-> FieldType "buffer" VkSparseBufferMemoryBindInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"buffer" VkSparseBufferMemoryBindInfo
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
"bindCount = " 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 (VkSparseBufferMemoryBindInfo
-> FieldType "bindCount" VkSparseBufferMemoryBindInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"bindCount" VkSparseBufferMemoryBindInfo
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
"pBinds = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> Ptr VkSparseMemoryBind -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseBufferMemoryBindInfo
-> FieldType "pBinds" VkSparseBufferMemoryBindInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pBinds" VkSparseBufferMemoryBindInfo
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkSparseImageFormatProperties = VkSparseImageFormatProperties# Addr#
ByteArray#
instance Eq VkSparseImageFormatProperties where
(VkSparseImageFormatProperties# Addr#
a ByteArray#
_) == :: VkSparseImageFormatProperties
-> VkSparseImageFormatProperties -> Bool
==
x :: VkSparseImageFormatProperties
x@(VkSparseImageFormatProperties# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageFormatProperties -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageFormatProperties
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSparseImageFormatProperties where
(VkSparseImageFormatProperties# Addr#
a ByteArray#
_) compare :: VkSparseImageFormatProperties
-> VkSparseImageFormatProperties -> Ordering
`compare`
x :: VkSparseImageFormatProperties
x@(VkSparseImageFormatProperties# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageFormatProperties -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageFormatProperties
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSparseImageFormatProperties where
sizeOf :: VkSparseImageFormatProperties -> Int
sizeOf ~VkSparseImageFormatProperties
_ = (Int
20)
{-# LINE 234 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSparseImageFormatProperties -> Int
alignment ~VkSparseImageFormatProperties
_
= Int
4
{-# LINE 238 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSparseImageFormatProperties
-> IO VkSparseImageFormatProperties
peek = Ptr VkSparseImageFormatProperties
-> IO VkSparseImageFormatProperties
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSparseImageFormatProperties
-> VkSparseImageFormatProperties -> IO ()
poke = Ptr VkSparseImageFormatProperties
-> VkSparseImageFormatProperties -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSparseImageFormatProperties where
unsafeAddr :: VkSparseImageFormatProperties -> Addr#
unsafeAddr (VkSparseImageFormatProperties# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSparseImageFormatProperties -> ByteArray#
unsafeByteArray (VkSparseImageFormatProperties# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSparseImageFormatProperties
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSparseImageFormatProperties
VkSparseImageFormatProperties#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSparseImageFormatProperties where
type StructFields VkSparseImageFormatProperties =
'["aspectMask", "imageGranularity", "flags"]
type CUnionType VkSparseImageFormatProperties = 'False
type ReturnedOnly VkSparseImageFormatProperties = 'True
type StructExtends VkSparseImageFormatProperties = '[]
instance {-# OVERLAPPING #-}
HasField "aspectMask" VkSparseImageFormatProperties where
type FieldType "aspectMask" VkSparseImageFormatProperties =
VkImageAspectFlags
type FieldOptional "aspectMask" VkSparseImageFormatProperties =
'True
type FieldOffset "aspectMask" VkSparseImageFormatProperties =
(0)
{-# LINE 276 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "aspectMask" VkSparseImageFormatProperties =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 285 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "aspectMask" VkSparseImageFormatProperties where
{-# NOINLINE getField #-}
getField :: VkSparseImageFormatProperties
-> FieldType "aspectMask" VkSparseImageFormatProperties
getField VkSparseImageFormatProperties
x
= IO VkImageAspectFlags -> VkImageAspectFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageFormatProperties -> Int -> IO VkImageAspectFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageFormatProperties -> Ptr VkSparseImageFormatProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageFormatProperties
x) (Int
0))
{-# LINE 292 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageFormatProperties
-> IO (FieldType "aspectMask" VkSparseImageFormatProperties)
readField Ptr VkSparseImageFormatProperties
p
= Ptr VkSparseImageFormatProperties -> Int -> IO VkImageAspectFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageFormatProperties
p (Int
0)
{-# LINE 296 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "aspectMask" VkSparseImageFormatProperties where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageFormatProperties
-> FieldType "aspectMask" VkSparseImageFormatProperties -> IO ()
writeField Ptr VkSparseImageFormatProperties
p
= Ptr VkSparseImageFormatProperties
-> Int -> VkImageAspectFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageFormatProperties
p (Int
0)
{-# LINE 302 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "imageGranularity" VkSparseImageFormatProperties where
type FieldType "imageGranularity" VkSparseImageFormatProperties =
VkExtent3D
type FieldOptional "imageGranularity" VkSparseImageFormatProperties
= 'False
type FieldOffset "imageGranularity" VkSparseImageFormatProperties =
(4)
{-# LINE 311 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "imageGranularity" VkSparseImageFormatProperties
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
4)
{-# LINE 320 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "imageGranularity" VkSparseImageFormatProperties where
{-# NOINLINE getField #-}
getField :: VkSparseImageFormatProperties
-> FieldType "imageGranularity" VkSparseImageFormatProperties
getField VkSparseImageFormatProperties
x
= IO VkExtent3D -> VkExtent3D
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageFormatProperties -> Int -> IO VkExtent3D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageFormatProperties -> Ptr VkSparseImageFormatProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageFormatProperties
x) (Int
4))
{-# LINE 327 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageFormatProperties
-> IO (FieldType "imageGranularity" VkSparseImageFormatProperties)
readField Ptr VkSparseImageFormatProperties
p
= Ptr VkSparseImageFormatProperties -> Int -> IO VkExtent3D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageFormatProperties
p (Int
4)
{-# LINE 331 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "imageGranularity" VkSparseImageFormatProperties
where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageFormatProperties
-> FieldType "imageGranularity" VkSparseImageFormatProperties
-> IO ()
writeField Ptr VkSparseImageFormatProperties
p
= Ptr VkSparseImageFormatProperties -> Int -> VkExtent3D -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageFormatProperties
p (Int
4)
{-# LINE 338 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "flags" VkSparseImageFormatProperties where
type FieldType "flags" VkSparseImageFormatProperties =
VkSparseImageFormatFlags
type FieldOptional "flags" VkSparseImageFormatProperties = 'True
type FieldOffset "flags" VkSparseImageFormatProperties =
(16)
{-# LINE 346 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "flags" VkSparseImageFormatProperties = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 354 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "flags" VkSparseImageFormatProperties where
{-# NOINLINE getField #-}
getField :: VkSparseImageFormatProperties
-> FieldType "flags" VkSparseImageFormatProperties
getField VkSparseImageFormatProperties
x
= IO VkSparseImageFormatFlags -> VkSparseImageFormatFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageFormatProperties
-> Int -> IO VkSparseImageFormatFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageFormatProperties -> Ptr VkSparseImageFormatProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageFormatProperties
x) (Int
16))
{-# LINE 361 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageFormatProperties
-> IO (FieldType "flags" VkSparseImageFormatProperties)
readField Ptr VkSparseImageFormatProperties
p
= Ptr VkSparseImageFormatProperties
-> Int -> IO VkSparseImageFormatFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageFormatProperties
p (Int
16)
{-# LINE 365 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "flags" VkSparseImageFormatProperties where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageFormatProperties
-> FieldType "flags" VkSparseImageFormatProperties -> IO ()
writeField Ptr VkSparseImageFormatProperties
p
= Ptr VkSparseImageFormatProperties
-> Int -> VkSparseImageFormatFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageFormatProperties
p (Int
16)
{-# LINE 371 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance Show VkSparseImageFormatProperties where
showsPrec :: Int -> VkSparseImageFormatProperties -> ShowS
showsPrec Int
d VkSparseImageFormatProperties
x
= String -> ShowS
showString String
"VkSparseImageFormatProperties {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
"aspectMask = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkImageAspectFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageFormatProperties
-> FieldType "aspectMask" VkSparseImageFormatProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"aspectMask" VkSparseImageFormatProperties
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
"imageGranularity = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkExtent3D -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageFormatProperties
-> FieldType "imageGranularity" VkSparseImageFormatProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"imageGranularity" VkSparseImageFormatProperties
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 -> VkSparseImageFormatFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageFormatProperties
-> FieldType "flags" VkSparseImageFormatProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkSparseImageFormatProperties
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkSparseImageFormatProperties2 = VkSparseImageFormatProperties2# Addr#
ByteArray#
instance Eq VkSparseImageFormatProperties2 where
(VkSparseImageFormatProperties2# Addr#
a ByteArray#
_) == :: VkSparseImageFormatProperties2
-> VkSparseImageFormatProperties2 -> Bool
==
x :: VkSparseImageFormatProperties2
x@(VkSparseImageFormatProperties2# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageFormatProperties2 -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageFormatProperties2
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSparseImageFormatProperties2 where
(VkSparseImageFormatProperties2# Addr#
a ByteArray#
_) compare :: VkSparseImageFormatProperties2
-> VkSparseImageFormatProperties2 -> Ordering
`compare`
x :: VkSparseImageFormatProperties2
x@(VkSparseImageFormatProperties2# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageFormatProperties2 -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageFormatProperties2
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSparseImageFormatProperties2 where
sizeOf :: VkSparseImageFormatProperties2 -> Int
sizeOf ~VkSparseImageFormatProperties2
_ = (Int
40)
{-# LINE 409 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSparseImageFormatProperties2 -> Int
alignment ~VkSparseImageFormatProperties2
_
= Int
8
{-# LINE 413 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSparseImageFormatProperties2
-> IO VkSparseImageFormatProperties2
peek = Ptr VkSparseImageFormatProperties2
-> IO VkSparseImageFormatProperties2
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSparseImageFormatProperties2
-> VkSparseImageFormatProperties2 -> IO ()
poke = Ptr VkSparseImageFormatProperties2
-> VkSparseImageFormatProperties2 -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSparseImageFormatProperties2 where
unsafeAddr :: VkSparseImageFormatProperties2 -> Addr#
unsafeAddr (VkSparseImageFormatProperties2# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSparseImageFormatProperties2 -> ByteArray#
unsafeByteArray (VkSparseImageFormatProperties2# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSparseImageFormatProperties2
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSparseImageFormatProperties2
VkSparseImageFormatProperties2#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSparseImageFormatProperties2 where
type StructFields VkSparseImageFormatProperties2 =
'["sType", "pNext", "properties"]
type CUnionType VkSparseImageFormatProperties2 = 'False
type ReturnedOnly VkSparseImageFormatProperties2 = 'True
type StructExtends VkSparseImageFormatProperties2 = '[]
instance {-# OVERLAPPING #-}
HasField "sType" VkSparseImageFormatProperties2 where
type FieldType "sType" VkSparseImageFormatProperties2 =
VkStructureType
type FieldOptional "sType" VkSparseImageFormatProperties2 = 'False
type FieldOffset "sType" VkSparseImageFormatProperties2 =
(0)
{-# LINE 450 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "sType" VkSparseImageFormatProperties2 = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 458 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkSparseImageFormatProperties2 where
{-# NOINLINE getField #-}
getField :: VkSparseImageFormatProperties2
-> FieldType "sType" VkSparseImageFormatProperties2
getField VkSparseImageFormatProperties2
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageFormatProperties2 -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageFormatProperties2
-> Ptr VkSparseImageFormatProperties2
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageFormatProperties2
x) (Int
0))
{-# LINE 465 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageFormatProperties2
-> IO (FieldType "sType" VkSparseImageFormatProperties2)
readField Ptr VkSparseImageFormatProperties2
p
= Ptr VkSparseImageFormatProperties2 -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageFormatProperties2
p (Int
0)
{-# LINE 469 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkSparseImageFormatProperties2 where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageFormatProperties2
-> FieldType "sType" VkSparseImageFormatProperties2 -> IO ()
writeField Ptr VkSparseImageFormatProperties2
p
= Ptr VkSparseImageFormatProperties2
-> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageFormatProperties2
p (Int
0)
{-# LINE 475 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkSparseImageFormatProperties2 where
type FieldType "pNext" VkSparseImageFormatProperties2 = Ptr Void
type FieldOptional "pNext" VkSparseImageFormatProperties2 = 'False
type FieldOffset "pNext" VkSparseImageFormatProperties2 =
(8)
{-# LINE 482 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "pNext" VkSparseImageFormatProperties2 = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 490 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkSparseImageFormatProperties2 where
{-# NOINLINE getField #-}
getField :: VkSparseImageFormatProperties2
-> FieldType "pNext" VkSparseImageFormatProperties2
getField VkSparseImageFormatProperties2
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageFormatProperties2 -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageFormatProperties2
-> Ptr VkSparseImageFormatProperties2
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageFormatProperties2
x) (Int
8))
{-# LINE 497 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageFormatProperties2
-> IO (FieldType "pNext" VkSparseImageFormatProperties2)
readField Ptr VkSparseImageFormatProperties2
p
= Ptr VkSparseImageFormatProperties2 -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageFormatProperties2
p (Int
8)
{-# LINE 501 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkSparseImageFormatProperties2 where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageFormatProperties2
-> FieldType "pNext" VkSparseImageFormatProperties2 -> IO ()
writeField Ptr VkSparseImageFormatProperties2
p
= Ptr VkSparseImageFormatProperties2 -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageFormatProperties2
p (Int
8)
{-# LINE 507 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "properties" VkSparseImageFormatProperties2 where
type FieldType "properties" VkSparseImageFormatProperties2 =
VkSparseImageFormatProperties
type FieldOptional "properties" VkSparseImageFormatProperties2 =
'False
type FieldOffset "properties" VkSparseImageFormatProperties2 =
(16)
{-# LINE 516 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "properties" VkSparseImageFormatProperties2 =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 525 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "properties" VkSparseImageFormatProperties2 where
{-# NOINLINE getField #-}
getField :: VkSparseImageFormatProperties2
-> FieldType "properties" VkSparseImageFormatProperties2
getField VkSparseImageFormatProperties2
x
= IO VkSparseImageFormatProperties -> VkSparseImageFormatProperties
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageFormatProperties2
-> Int -> IO VkSparseImageFormatProperties
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageFormatProperties2
-> Ptr VkSparseImageFormatProperties2
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageFormatProperties2
x) (Int
16))
{-# LINE 532 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageFormatProperties2
-> IO (FieldType "properties" VkSparseImageFormatProperties2)
readField Ptr VkSparseImageFormatProperties2
p
= Ptr VkSparseImageFormatProperties2
-> Int -> IO VkSparseImageFormatProperties
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageFormatProperties2
p (Int
16)
{-# LINE 536 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "properties" VkSparseImageFormatProperties2 where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageFormatProperties2
-> FieldType "properties" VkSparseImageFormatProperties2 -> IO ()
writeField Ptr VkSparseImageFormatProperties2
p
= Ptr VkSparseImageFormatProperties2
-> Int -> VkSparseImageFormatProperties -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageFormatProperties2
p (Int
16)
{-# LINE 542 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance Show VkSparseImageFormatProperties2 where
showsPrec :: Int -> VkSparseImageFormatProperties2 -> ShowS
showsPrec Int
d VkSparseImageFormatProperties2
x
= String -> ShowS
showString String
"VkSparseImageFormatProperties2 {" 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 (VkSparseImageFormatProperties2
-> FieldType "sType" VkSparseImageFormatProperties2
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkSparseImageFormatProperties2
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 (VkSparseImageFormatProperties2
-> FieldType "pNext" VkSparseImageFormatProperties2
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkSparseImageFormatProperties2
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
"properties = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkSparseImageFormatProperties -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageFormatProperties2
-> FieldType "properties" VkSparseImageFormatProperties2
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"properties" VkSparseImageFormatProperties2
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
type VkSparseImageFormatProperties2KHR =
VkSparseImageFormatProperties2
data VkSparseImageMemoryBind = VkSparseImageMemoryBind# Addr#
ByteArray#
instance Eq VkSparseImageMemoryBind where
(VkSparseImageMemoryBind# Addr#
a ByteArray#
_) == :: VkSparseImageMemoryBind -> VkSparseImageMemoryBind -> Bool
== x :: VkSparseImageMemoryBind
x@(VkSparseImageMemoryBind# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageMemoryBind -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageMemoryBind
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSparseImageMemoryBind where
(VkSparseImageMemoryBind# Addr#
a ByteArray#
_) compare :: VkSparseImageMemoryBind -> VkSparseImageMemoryBind -> Ordering
`compare`
x :: VkSparseImageMemoryBind
x@(VkSparseImageMemoryBind# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageMemoryBind -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageMemoryBind
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSparseImageMemoryBind where
sizeOf :: VkSparseImageMemoryBind -> Int
sizeOf ~VkSparseImageMemoryBind
_ = (Int
64)
{-# LINE 586 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSparseImageMemoryBind -> Int
alignment ~VkSparseImageMemoryBind
_ = Int
8
{-# LINE 589 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSparseImageMemoryBind -> IO VkSparseImageMemoryBind
peek = Ptr VkSparseImageMemoryBind -> IO VkSparseImageMemoryBind
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSparseImageMemoryBind -> VkSparseImageMemoryBind -> IO ()
poke = Ptr VkSparseImageMemoryBind -> VkSparseImageMemoryBind -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSparseImageMemoryBind where
unsafeAddr :: VkSparseImageMemoryBind -> Addr#
unsafeAddr (VkSparseImageMemoryBind# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSparseImageMemoryBind -> ByteArray#
unsafeByteArray (VkSparseImageMemoryBind# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSparseImageMemoryBind
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSparseImageMemoryBind
VkSparseImageMemoryBind# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSparseImageMemoryBind where
type StructFields VkSparseImageMemoryBind =
'["subresource", "offset", "extent", "memory", "memoryOffset",
"flags"]
type CUnionType VkSparseImageMemoryBind = 'False
type ReturnedOnly VkSparseImageMemoryBind = 'False
type StructExtends VkSparseImageMemoryBind = '[]
instance {-# OVERLAPPING #-}
HasField "subresource" VkSparseImageMemoryBind where
type FieldType "subresource" VkSparseImageMemoryBind =
VkImageSubresource
type FieldOptional "subresource" VkSparseImageMemoryBind = 'False
type FieldOffset "subresource" VkSparseImageMemoryBind =
(0)
{-# LINE 625 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "subresource" VkSparseImageMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 633 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "subresource" VkSparseImageMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryBind
-> FieldType "subresource" VkSparseImageMemoryBind
getField VkSparseImageMemoryBind
x
= IO VkImageSubresource -> VkImageSubresource
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryBind -> Int -> IO VkImageSubresource
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryBind -> Ptr VkSparseImageMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryBind
x) (Int
0))
{-# LINE 640 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryBind
-> IO (FieldType "subresource" VkSparseImageMemoryBind)
readField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> IO VkImageSubresource
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryBind
p (Int
0)
{-# LINE 644 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "subresource" VkSparseImageMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryBind
-> FieldType "subresource" VkSparseImageMemoryBind -> IO ()
writeField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> VkImageSubresource -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryBind
p (Int
0)
{-# LINE 650 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "offset" VkSparseImageMemoryBind where
type FieldType "offset" VkSparseImageMemoryBind = VkOffset3D
type FieldOptional "offset" VkSparseImageMemoryBind = 'False
type FieldOffset "offset" VkSparseImageMemoryBind =
(12)
{-# LINE 657 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "offset" VkSparseImageMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
12)
{-# LINE 664 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "offset" VkSparseImageMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryBind
-> FieldType "offset" VkSparseImageMemoryBind
getField VkSparseImageMemoryBind
x
= IO VkOffset3D -> VkOffset3D
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryBind -> Int -> IO VkOffset3D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryBind -> Ptr VkSparseImageMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryBind
x) (Int
12))
{-# LINE 671 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryBind
-> IO (FieldType "offset" VkSparseImageMemoryBind)
readField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> IO VkOffset3D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryBind
p (Int
12)
{-# LINE 675 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "offset" VkSparseImageMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryBind
-> FieldType "offset" VkSparseImageMemoryBind -> IO ()
writeField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> VkOffset3D -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryBind
p (Int
12)
{-# LINE 681 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "extent" VkSparseImageMemoryBind where
type FieldType "extent" VkSparseImageMemoryBind = VkExtent3D
type FieldOptional "extent" VkSparseImageMemoryBind = 'False
type FieldOffset "extent" VkSparseImageMemoryBind =
(24)
{-# LINE 688 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "extent" VkSparseImageMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
24)
{-# LINE 695 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "extent" VkSparseImageMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryBind
-> FieldType "extent" VkSparseImageMemoryBind
getField VkSparseImageMemoryBind
x
= IO VkExtent3D -> VkExtent3D
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryBind -> Int -> IO VkExtent3D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryBind -> Ptr VkSparseImageMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryBind
x) (Int
24))
{-# LINE 702 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryBind
-> IO (FieldType "extent" VkSparseImageMemoryBind)
readField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> IO VkExtent3D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryBind
p (Int
24)
{-# LINE 706 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "extent" VkSparseImageMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryBind
-> FieldType "extent" VkSparseImageMemoryBind -> IO ()
writeField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> VkExtent3D -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryBind
p (Int
24)
{-# LINE 712 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "memory" VkSparseImageMemoryBind where
type FieldType "memory" VkSparseImageMemoryBind = VkDeviceMemory
type FieldOptional "memory" VkSparseImageMemoryBind = 'True
type FieldOffset "memory" VkSparseImageMemoryBind =
(40)
{-# LINE 719 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "memory" VkSparseImageMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
40)
{-# LINE 726 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "memory" VkSparseImageMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryBind
-> FieldType "memory" VkSparseImageMemoryBind
getField VkSparseImageMemoryBind
x
= IO VkDeviceMemory -> VkDeviceMemory
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryBind -> Int -> IO VkDeviceMemory
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryBind -> Ptr VkSparseImageMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryBind
x) (Int
40))
{-# LINE 733 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryBind
-> IO (FieldType "memory" VkSparseImageMemoryBind)
readField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> IO VkDeviceMemory
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryBind
p (Int
40)
{-# LINE 737 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "memory" VkSparseImageMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryBind
-> FieldType "memory" VkSparseImageMemoryBind -> IO ()
writeField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> VkDeviceMemory -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryBind
p (Int
40)
{-# LINE 743 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "memoryOffset" VkSparseImageMemoryBind where
type FieldType "memoryOffset" VkSparseImageMemoryBind =
VkDeviceSize
type FieldOptional "memoryOffset" VkSparseImageMemoryBind = 'False
type FieldOffset "memoryOffset" VkSparseImageMemoryBind =
(48)
{-# LINE 751 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "memoryOffset" VkSparseImageMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
48)
{-# LINE 759 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "memoryOffset" VkSparseImageMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryBind
-> FieldType "memoryOffset" VkSparseImageMemoryBind
getField VkSparseImageMemoryBind
x
= IO VkDeviceSize -> VkDeviceSize
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryBind -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryBind -> Ptr VkSparseImageMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryBind
x) (Int
48))
{-# LINE 766 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryBind
-> IO (FieldType "memoryOffset" VkSparseImageMemoryBind)
readField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryBind
p (Int
48)
{-# LINE 770 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "memoryOffset" VkSparseImageMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryBind
-> FieldType "memoryOffset" VkSparseImageMemoryBind -> IO ()
writeField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryBind
p (Int
48)
{-# LINE 776 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "flags" VkSparseImageMemoryBind where
type FieldType "flags" VkSparseImageMemoryBind =
VkSparseMemoryBindFlags
type FieldOptional "flags" VkSparseImageMemoryBind = 'True
type FieldOffset "flags" VkSparseImageMemoryBind =
(56)
{-# LINE 784 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "flags" VkSparseImageMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
56)
{-# LINE 791 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "flags" VkSparseImageMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryBind
-> FieldType "flags" VkSparseImageMemoryBind
getField VkSparseImageMemoryBind
x
= IO VkSparseMemoryBindFlags -> VkSparseMemoryBindFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryBind -> Int -> IO VkSparseMemoryBindFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryBind -> Ptr VkSparseImageMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryBind
x) (Int
56))
{-# LINE 798 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryBind
-> IO (FieldType "flags" VkSparseImageMemoryBind)
readField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind -> Int -> IO VkSparseMemoryBindFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryBind
p (Int
56)
{-# LINE 802 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "flags" VkSparseImageMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryBind
-> FieldType "flags" VkSparseImageMemoryBind -> IO ()
writeField Ptr VkSparseImageMemoryBind
p
= Ptr VkSparseImageMemoryBind
-> Int -> VkSparseMemoryBindFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryBind
p (Int
56)
{-# LINE 808 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance Show VkSparseImageMemoryBind where
showsPrec :: Int -> VkSparseImageMemoryBind -> ShowS
showsPrec Int
d VkSparseImageMemoryBind
x
= String -> ShowS
showString String
"VkSparseImageMemoryBind {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
"subresource = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkImageSubresource -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageMemoryBind
-> FieldType "subresource" VkSparseImageMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"subresource" VkSparseImageMemoryBind
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
"offset = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkOffset3D -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageMemoryBind
-> FieldType "offset" VkSparseImageMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"offset" VkSparseImageMemoryBind
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
"extent = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkExtent3D -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageMemoryBind
-> FieldType "extent" VkSparseImageMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"extent" VkSparseImageMemoryBind
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 (VkSparseImageMemoryBind
-> FieldType "memory" VkSparseImageMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"memory" VkSparseImageMemoryBind
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
"memoryOffset = " 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 (VkSparseImageMemoryBind
-> FieldType "memoryOffset" VkSparseImageMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"memoryOffset" VkSparseImageMemoryBind
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 -> VkSparseMemoryBindFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageMemoryBind
-> FieldType "flags" VkSparseImageMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkSparseImageMemoryBind
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkSparseImageMemoryBindInfo = VkSparseImageMemoryBindInfo# Addr#
ByteArray#
instance Eq VkSparseImageMemoryBindInfo where
(VkSparseImageMemoryBindInfo# Addr#
a ByteArray#
_) == :: VkSparseImageMemoryBindInfo -> VkSparseImageMemoryBindInfo -> Bool
==
x :: VkSparseImageMemoryBindInfo
x@(VkSparseImageMemoryBindInfo# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageMemoryBindInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageMemoryBindInfo
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSparseImageMemoryBindInfo where
(VkSparseImageMemoryBindInfo# Addr#
a ByteArray#
_) compare :: VkSparseImageMemoryBindInfo
-> VkSparseImageMemoryBindInfo -> Ordering
`compare`
x :: VkSparseImageMemoryBindInfo
x@(VkSparseImageMemoryBindInfo# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageMemoryBindInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageMemoryBindInfo
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSparseImageMemoryBindInfo where
sizeOf :: VkSparseImageMemoryBindInfo -> Int
sizeOf ~VkSparseImageMemoryBindInfo
_ = (Int
24)
{-# LINE 855 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSparseImageMemoryBindInfo -> Int
alignment ~VkSparseImageMemoryBindInfo
_ = Int
8
{-# LINE 858 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSparseImageMemoryBindInfo -> IO VkSparseImageMemoryBindInfo
peek = Ptr VkSparseImageMemoryBindInfo -> IO VkSparseImageMemoryBindInfo
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSparseImageMemoryBindInfo
-> VkSparseImageMemoryBindInfo -> IO ()
poke = Ptr VkSparseImageMemoryBindInfo
-> VkSparseImageMemoryBindInfo -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSparseImageMemoryBindInfo where
unsafeAddr :: VkSparseImageMemoryBindInfo -> Addr#
unsafeAddr (VkSparseImageMemoryBindInfo# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSparseImageMemoryBindInfo -> ByteArray#
unsafeByteArray (VkSparseImageMemoryBindInfo# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSparseImageMemoryBindInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSparseImageMemoryBindInfo
VkSparseImageMemoryBindInfo#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSparseImageMemoryBindInfo where
type StructFields VkSparseImageMemoryBindInfo =
'["image", "bindCount", "pBinds"]
type CUnionType VkSparseImageMemoryBindInfo = 'False
type ReturnedOnly VkSparseImageMemoryBindInfo = 'False
type StructExtends VkSparseImageMemoryBindInfo = '[]
instance {-# OVERLAPPING #-}
HasField "image" VkSparseImageMemoryBindInfo where
type FieldType "image" VkSparseImageMemoryBindInfo = VkImage
type FieldOptional "image" VkSparseImageMemoryBindInfo = 'False
type FieldOffset "image" VkSparseImageMemoryBindInfo =
(0)
{-# LINE 894 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "image" VkSparseImageMemoryBindInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 902 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "image" VkSparseImageMemoryBindInfo where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryBindInfo
-> FieldType "image" VkSparseImageMemoryBindInfo
getField VkSparseImageMemoryBindInfo
x
= IO VkImage -> VkImage
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryBindInfo -> Int -> IO VkImage
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryBindInfo -> Ptr VkSparseImageMemoryBindInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryBindInfo
x) (Int
0))
{-# LINE 909 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryBindInfo
-> IO (FieldType "image" VkSparseImageMemoryBindInfo)
readField Ptr VkSparseImageMemoryBindInfo
p
= Ptr VkSparseImageMemoryBindInfo -> Int -> IO VkImage
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryBindInfo
p (Int
0)
{-# LINE 913 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "image" VkSparseImageMemoryBindInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryBindInfo
-> FieldType "image" VkSparseImageMemoryBindInfo -> IO ()
writeField Ptr VkSparseImageMemoryBindInfo
p
= Ptr VkSparseImageMemoryBindInfo -> Int -> VkImage -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryBindInfo
p (Int
0)
{-# LINE 919 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "bindCount" VkSparseImageMemoryBindInfo where
type FieldType "bindCount" VkSparseImageMemoryBindInfo = Word32
type FieldOptional "bindCount" VkSparseImageMemoryBindInfo = 'False
type FieldOffset "bindCount" VkSparseImageMemoryBindInfo =
(8)
{-# LINE 926 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "bindCount" VkSparseImageMemoryBindInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 934 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "bindCount" VkSparseImageMemoryBindInfo where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryBindInfo
-> FieldType "bindCount" VkSparseImageMemoryBindInfo
getField VkSparseImageMemoryBindInfo
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryBindInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryBindInfo -> Ptr VkSparseImageMemoryBindInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryBindInfo
x) (Int
8))
{-# LINE 941 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryBindInfo
-> IO (FieldType "bindCount" VkSparseImageMemoryBindInfo)
readField Ptr VkSparseImageMemoryBindInfo
p
= Ptr VkSparseImageMemoryBindInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryBindInfo
p (Int
8)
{-# LINE 945 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "bindCount" VkSparseImageMemoryBindInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryBindInfo
-> FieldType "bindCount" VkSparseImageMemoryBindInfo -> IO ()
writeField Ptr VkSparseImageMemoryBindInfo
p
= Ptr VkSparseImageMemoryBindInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryBindInfo
p (Int
8)
{-# LINE 951 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pBinds" VkSparseImageMemoryBindInfo where
type FieldType "pBinds" VkSparseImageMemoryBindInfo =
Ptr VkSparseImageMemoryBind
type FieldOptional "pBinds" VkSparseImageMemoryBindInfo = 'False
type FieldOffset "pBinds" VkSparseImageMemoryBindInfo =
(16)
{-# LINE 959 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "pBinds" VkSparseImageMemoryBindInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 967 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pBinds" VkSparseImageMemoryBindInfo where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryBindInfo
-> FieldType "pBinds" VkSparseImageMemoryBindInfo
getField VkSparseImageMemoryBindInfo
x
= IO (Ptr VkSparseImageMemoryBind) -> Ptr VkSparseImageMemoryBind
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryBindInfo
-> Int -> IO (Ptr VkSparseImageMemoryBind)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryBindInfo -> Ptr VkSparseImageMemoryBindInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryBindInfo
x) (Int
16))
{-# LINE 974 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryBindInfo
-> IO (FieldType "pBinds" VkSparseImageMemoryBindInfo)
readField Ptr VkSparseImageMemoryBindInfo
p
= Ptr VkSparseImageMemoryBindInfo
-> Int -> IO (Ptr VkSparseImageMemoryBind)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryBindInfo
p (Int
16)
{-# LINE 978 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pBinds" VkSparseImageMemoryBindInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryBindInfo
-> FieldType "pBinds" VkSparseImageMemoryBindInfo -> IO ()
writeField Ptr VkSparseImageMemoryBindInfo
p
= Ptr VkSparseImageMemoryBindInfo
-> Int -> Ptr VkSparseImageMemoryBind -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryBindInfo
p (Int
16)
{-# LINE 984 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance Show VkSparseImageMemoryBindInfo where
showsPrec :: Int -> VkSparseImageMemoryBindInfo -> ShowS
showsPrec Int
d VkSparseImageMemoryBindInfo
x
= String -> ShowS
showString String
"VkSparseImageMemoryBindInfo {" 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 (VkSparseImageMemoryBindInfo
-> FieldType "image" VkSparseImageMemoryBindInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"image" VkSparseImageMemoryBindInfo
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
"bindCount = " 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 (VkSparseImageMemoryBindInfo
-> FieldType "bindCount" VkSparseImageMemoryBindInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"bindCount" VkSparseImageMemoryBindInfo
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
"pBinds = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> Ptr VkSparseImageMemoryBind -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageMemoryBindInfo
-> FieldType "pBinds" VkSparseImageMemoryBindInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pBinds" VkSparseImageMemoryBindInfo
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkSparseImageMemoryRequirements = VkSparseImageMemoryRequirements# Addr#
ByteArray#
instance Eq VkSparseImageMemoryRequirements where
(VkSparseImageMemoryRequirements# Addr#
a ByteArray#
_) == :: VkSparseImageMemoryRequirements
-> VkSparseImageMemoryRequirements -> Bool
==
x :: VkSparseImageMemoryRequirements
x@(VkSparseImageMemoryRequirements# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageMemoryRequirements -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageMemoryRequirements
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSparseImageMemoryRequirements where
(VkSparseImageMemoryRequirements# Addr#
a ByteArray#
_) compare :: VkSparseImageMemoryRequirements
-> VkSparseImageMemoryRequirements -> Ordering
`compare`
x :: VkSparseImageMemoryRequirements
x@(VkSparseImageMemoryRequirements# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageMemoryRequirements -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageMemoryRequirements
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSparseImageMemoryRequirements where
sizeOf :: VkSparseImageMemoryRequirements -> Int
sizeOf ~VkSparseImageMemoryRequirements
_ = (Int
48)
{-# LINE 1024 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSparseImageMemoryRequirements -> Int
alignment ~VkSparseImageMemoryRequirements
_
= Int
8
{-# LINE 1028 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSparseImageMemoryRequirements
-> IO VkSparseImageMemoryRequirements
peek = Ptr VkSparseImageMemoryRequirements
-> IO VkSparseImageMemoryRequirements
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSparseImageMemoryRequirements
-> VkSparseImageMemoryRequirements -> IO ()
poke = Ptr VkSparseImageMemoryRequirements
-> VkSparseImageMemoryRequirements -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSparseImageMemoryRequirements where
unsafeAddr :: VkSparseImageMemoryRequirements -> Addr#
unsafeAddr (VkSparseImageMemoryRequirements# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSparseImageMemoryRequirements -> ByteArray#
unsafeByteArray (VkSparseImageMemoryRequirements# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSparseImageMemoryRequirements
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSparseImageMemoryRequirements
VkSparseImageMemoryRequirements#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSparseImageMemoryRequirements where
type StructFields VkSparseImageMemoryRequirements =
'["formatProperties", "imageMipTailFirstLod", "imageMipTailSize",
"imageMipTailOffset", "imageMipTailStride"]
type CUnionType VkSparseImageMemoryRequirements = 'False
type ReturnedOnly VkSparseImageMemoryRequirements = 'True
type StructExtends VkSparseImageMemoryRequirements = '[]
instance {-# OVERLAPPING #-}
HasField "formatProperties" VkSparseImageMemoryRequirements where
type FieldType "formatProperties" VkSparseImageMemoryRequirements =
VkSparseImageFormatProperties
type FieldOptional "formatProperties"
VkSparseImageMemoryRequirements
= 'False
type FieldOffset "formatProperties" VkSparseImageMemoryRequirements
=
(0)
{-# LINE 1069 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "formatProperties"
VkSparseImageMemoryRequirements
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 1079 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "formatProperties" VkSparseImageMemoryRequirements
where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryRequirements
-> FieldType "formatProperties" VkSparseImageMemoryRequirements
getField VkSparseImageMemoryRequirements
x
= IO VkSparseImageFormatProperties -> VkSparseImageFormatProperties
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryRequirements
-> Int -> IO VkSparseImageFormatProperties
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryRequirements
-> Ptr VkSparseImageMemoryRequirements
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryRequirements
x) (Int
0))
{-# LINE 1087 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryRequirements
-> IO
(FieldType "formatProperties" VkSparseImageMemoryRequirements)
readField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements
-> Int -> IO VkSparseImageFormatProperties
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryRequirements
p (Int
0)
{-# LINE 1091 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "formatProperties" VkSparseImageMemoryRequirements
where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryRequirements
-> FieldType "formatProperties" VkSparseImageMemoryRequirements
-> IO ()
writeField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements
-> Int -> VkSparseImageFormatProperties -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryRequirements
p (Int
0)
{-# LINE 1098 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "imageMipTailFirstLod" VkSparseImageMemoryRequirements
where
type FieldType "imageMipTailFirstLod"
VkSparseImageMemoryRequirements
= Word32
type FieldOptional "imageMipTailFirstLod"
VkSparseImageMemoryRequirements
= 'False
type FieldOffset "imageMipTailFirstLod"
VkSparseImageMemoryRequirements
=
(20)
{-# LINE 1112 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "imageMipTailFirstLod"
VkSparseImageMemoryRequirements
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
20)
{-# LINE 1122 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "imageMipTailFirstLod" VkSparseImageMemoryRequirements
where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryRequirements
-> FieldType "imageMipTailFirstLod" VkSparseImageMemoryRequirements
getField VkSparseImageMemoryRequirements
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryRequirements -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryRequirements
-> Ptr VkSparseImageMemoryRequirements
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryRequirements
x) (Int
20))
{-# LINE 1130 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryRequirements
-> IO
(FieldType "imageMipTailFirstLod" VkSparseImageMemoryRequirements)
readField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryRequirements
p (Int
20)
{-# LINE 1134 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "imageMipTailFirstLod"
VkSparseImageMemoryRequirements
where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryRequirements
-> FieldType "imageMipTailFirstLod" VkSparseImageMemoryRequirements
-> IO ()
writeField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryRequirements
p (Int
20)
{-# LINE 1142 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "imageMipTailSize" VkSparseImageMemoryRequirements where
type FieldType "imageMipTailSize" VkSparseImageMemoryRequirements =
VkDeviceSize
type FieldOptional "imageMipTailSize"
VkSparseImageMemoryRequirements
= 'False
type FieldOffset "imageMipTailSize" VkSparseImageMemoryRequirements
=
(24)
{-# LINE 1153 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "imageMipTailSize"
VkSparseImageMemoryRequirements
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
24)
{-# LINE 1163 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "imageMipTailSize" VkSparseImageMemoryRequirements
where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryRequirements
-> FieldType "imageMipTailSize" VkSparseImageMemoryRequirements
getField VkSparseImageMemoryRequirements
x
= IO VkDeviceSize -> VkDeviceSize
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryRequirements -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryRequirements
-> Ptr VkSparseImageMemoryRequirements
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryRequirements
x) (Int
24))
{-# LINE 1171 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryRequirements
-> IO
(FieldType "imageMipTailSize" VkSparseImageMemoryRequirements)
readField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryRequirements
p (Int
24)
{-# LINE 1175 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "imageMipTailSize" VkSparseImageMemoryRequirements
where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryRequirements
-> FieldType "imageMipTailSize" VkSparseImageMemoryRequirements
-> IO ()
writeField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryRequirements
p (Int
24)
{-# LINE 1182 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "imageMipTailOffset" VkSparseImageMemoryRequirements where
type FieldType "imageMipTailOffset" VkSparseImageMemoryRequirements
= VkDeviceSize
type FieldOptional "imageMipTailOffset"
VkSparseImageMemoryRequirements
= 'False
type FieldOffset "imageMipTailOffset"
VkSparseImageMemoryRequirements
=
(32)
{-# LINE 1194 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "imageMipTailOffset"
VkSparseImageMemoryRequirements
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
32)
{-# LINE 1204 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "imageMipTailOffset" VkSparseImageMemoryRequirements
where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryRequirements
-> FieldType "imageMipTailOffset" VkSparseImageMemoryRequirements
getField VkSparseImageMemoryRequirements
x
= IO VkDeviceSize -> VkDeviceSize
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryRequirements -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryRequirements
-> Ptr VkSparseImageMemoryRequirements
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryRequirements
x) (Int
32))
{-# LINE 1212 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryRequirements
-> IO
(FieldType "imageMipTailOffset" VkSparseImageMemoryRequirements)
readField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryRequirements
p (Int
32)
{-# LINE 1216 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "imageMipTailOffset" VkSparseImageMemoryRequirements
where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryRequirements
-> FieldType "imageMipTailOffset" VkSparseImageMemoryRequirements
-> IO ()
writeField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryRequirements
p (Int
32)
{-# LINE 1223 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "imageMipTailStride" VkSparseImageMemoryRequirements where
type FieldType "imageMipTailStride" VkSparseImageMemoryRequirements
= VkDeviceSize
type FieldOptional "imageMipTailStride"
VkSparseImageMemoryRequirements
= 'False
type FieldOffset "imageMipTailStride"
VkSparseImageMemoryRequirements
=
(40)
{-# LINE 1235 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "imageMipTailStride"
VkSparseImageMemoryRequirements
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
40)
{-# LINE 1245 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "imageMipTailStride" VkSparseImageMemoryRequirements
where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryRequirements
-> FieldType "imageMipTailStride" VkSparseImageMemoryRequirements
getField VkSparseImageMemoryRequirements
x
= IO VkDeviceSize -> VkDeviceSize
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryRequirements -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryRequirements
-> Ptr VkSparseImageMemoryRequirements
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryRequirements
x) (Int
40))
{-# LINE 1253 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryRequirements
-> IO
(FieldType "imageMipTailStride" VkSparseImageMemoryRequirements)
readField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryRequirements
p (Int
40)
{-# LINE 1257 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "imageMipTailStride" VkSparseImageMemoryRequirements
where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryRequirements
-> FieldType "imageMipTailStride" VkSparseImageMemoryRequirements
-> IO ()
writeField Ptr VkSparseImageMemoryRequirements
p
= Ptr VkSparseImageMemoryRequirements -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryRequirements
p (Int
40)
{-# LINE 1264 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance Show VkSparseImageMemoryRequirements where
showsPrec :: Int -> VkSparseImageMemoryRequirements -> ShowS
showsPrec Int
d VkSparseImageMemoryRequirements
x
= String -> ShowS
showString String
"VkSparseImageMemoryRequirements {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
"formatProperties = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkSparseImageFormatProperties -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageMemoryRequirements
-> FieldType "formatProperties" VkSparseImageMemoryRequirements
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"formatProperties" VkSparseImageMemoryRequirements
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
"imageMipTailFirstLod = " 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 (VkSparseImageMemoryRequirements
-> FieldType "imageMipTailFirstLod" VkSparseImageMemoryRequirements
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"imageMipTailFirstLod" VkSparseImageMemoryRequirements
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
"imageMipTailSize = " 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 (VkSparseImageMemoryRequirements
-> FieldType "imageMipTailSize" VkSparseImageMemoryRequirements
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"imageMipTailSize" VkSparseImageMemoryRequirements
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
"imageMipTailOffset = " 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 (VkSparseImageMemoryRequirements
-> FieldType "imageMipTailOffset" VkSparseImageMemoryRequirements
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"imageMipTailOffset" VkSparseImageMemoryRequirements
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
"imageMipTailStride = " 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 (VkSparseImageMemoryRequirements
-> FieldType "imageMipTailStride" VkSparseImageMemoryRequirements
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"imageMipTailStride" VkSparseImageMemoryRequirements
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Char -> ShowS
showChar Char
'}'
data VkSparseImageMemoryRequirements2 = VkSparseImageMemoryRequirements2# Addr#
ByteArray#
instance Eq VkSparseImageMemoryRequirements2 where
(VkSparseImageMemoryRequirements2# Addr#
a ByteArray#
_) == :: VkSparseImageMemoryRequirements2
-> VkSparseImageMemoryRequirements2 -> Bool
==
x :: VkSparseImageMemoryRequirements2
x@(VkSparseImageMemoryRequirements2# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageMemoryRequirements2 -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageMemoryRequirements2
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSparseImageMemoryRequirements2 where
(VkSparseImageMemoryRequirements2# Addr#
a ByteArray#
_) compare :: VkSparseImageMemoryRequirements2
-> VkSparseImageMemoryRequirements2 -> Ordering
`compare`
x :: VkSparseImageMemoryRequirements2
x@(VkSparseImageMemoryRequirements2# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageMemoryRequirements2 -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageMemoryRequirements2
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSparseImageMemoryRequirements2 where
sizeOf :: VkSparseImageMemoryRequirements2 -> Int
sizeOf ~VkSparseImageMemoryRequirements2
_ = (Int
64)
{-# LINE 1310 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSparseImageMemoryRequirements2 -> Int
alignment ~VkSparseImageMemoryRequirements2
_
= Int
8
{-# LINE 1314 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSparseImageMemoryRequirements2
-> IO VkSparseImageMemoryRequirements2
peek = Ptr VkSparseImageMemoryRequirements2
-> IO VkSparseImageMemoryRequirements2
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSparseImageMemoryRequirements2
-> VkSparseImageMemoryRequirements2 -> IO ()
poke = Ptr VkSparseImageMemoryRequirements2
-> VkSparseImageMemoryRequirements2 -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSparseImageMemoryRequirements2 where
unsafeAddr :: VkSparseImageMemoryRequirements2 -> Addr#
unsafeAddr (VkSparseImageMemoryRequirements2# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSparseImageMemoryRequirements2 -> ByteArray#
unsafeByteArray (VkSparseImageMemoryRequirements2# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSparseImageMemoryRequirements2
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSparseImageMemoryRequirements2
VkSparseImageMemoryRequirements2#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSparseImageMemoryRequirements2 where
type StructFields VkSparseImageMemoryRequirements2 =
'["sType", "pNext", "memoryRequirements"]
type CUnionType VkSparseImageMemoryRequirements2 = 'False
type ReturnedOnly VkSparseImageMemoryRequirements2 = 'True
type StructExtends VkSparseImageMemoryRequirements2 = '[]
instance {-# OVERLAPPING #-}
HasField "sType" VkSparseImageMemoryRequirements2 where
type FieldType "sType" VkSparseImageMemoryRequirements2 =
VkStructureType
type FieldOptional "sType" VkSparseImageMemoryRequirements2 =
'False
type FieldOffset "sType" VkSparseImageMemoryRequirements2 =
(0)
{-# LINE 1352 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "sType" VkSparseImageMemoryRequirements2 = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 1360 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkSparseImageMemoryRequirements2 where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryRequirements2
-> FieldType "sType" VkSparseImageMemoryRequirements2
getField VkSparseImageMemoryRequirements2
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryRequirements2 -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryRequirements2
-> Ptr VkSparseImageMemoryRequirements2
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryRequirements2
x) (Int
0))
{-# LINE 1367 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryRequirements2
-> IO (FieldType "sType" VkSparseImageMemoryRequirements2)
readField Ptr VkSparseImageMemoryRequirements2
p
= Ptr VkSparseImageMemoryRequirements2 -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryRequirements2
p (Int
0)
{-# LINE 1371 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkSparseImageMemoryRequirements2 where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryRequirements2
-> FieldType "sType" VkSparseImageMemoryRequirements2 -> IO ()
writeField Ptr VkSparseImageMemoryRequirements2
p
= Ptr VkSparseImageMemoryRequirements2
-> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryRequirements2
p (Int
0)
{-# LINE 1377 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkSparseImageMemoryRequirements2 where
type FieldType "pNext" VkSparseImageMemoryRequirements2 = Ptr Void
type FieldOptional "pNext" VkSparseImageMemoryRequirements2 =
'False
type FieldOffset "pNext" VkSparseImageMemoryRequirements2 =
(8)
{-# LINE 1385 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "pNext" VkSparseImageMemoryRequirements2 = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 1393 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkSparseImageMemoryRequirements2 where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryRequirements2
-> FieldType "pNext" VkSparseImageMemoryRequirements2
getField VkSparseImageMemoryRequirements2
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryRequirements2 -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryRequirements2
-> Ptr VkSparseImageMemoryRequirements2
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryRequirements2
x) (Int
8))
{-# LINE 1400 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryRequirements2
-> IO (FieldType "pNext" VkSparseImageMemoryRequirements2)
readField Ptr VkSparseImageMemoryRequirements2
p
= Ptr VkSparseImageMemoryRequirements2 -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryRequirements2
p (Int
8)
{-# LINE 1404 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkSparseImageMemoryRequirements2 where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryRequirements2
-> FieldType "pNext" VkSparseImageMemoryRequirements2 -> IO ()
writeField Ptr VkSparseImageMemoryRequirements2
p
= Ptr VkSparseImageMemoryRequirements2 -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryRequirements2
p (Int
8)
{-# LINE 1410 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "memoryRequirements" VkSparseImageMemoryRequirements2
where
type FieldType "memoryRequirements"
VkSparseImageMemoryRequirements2
= VkSparseImageMemoryRequirements
type FieldOptional "memoryRequirements"
VkSparseImageMemoryRequirements2
= 'False
type FieldOffset "memoryRequirements"
VkSparseImageMemoryRequirements2
=
(16)
{-# LINE 1424 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "memoryRequirements"
VkSparseImageMemoryRequirements2
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 1434 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "memoryRequirements" VkSparseImageMemoryRequirements2
where
{-# NOINLINE getField #-}
getField :: VkSparseImageMemoryRequirements2
-> FieldType "memoryRequirements" VkSparseImageMemoryRequirements2
getField VkSparseImageMemoryRequirements2
x
= IO VkSparseImageMemoryRequirements
-> VkSparseImageMemoryRequirements
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageMemoryRequirements2
-> Int -> IO VkSparseImageMemoryRequirements
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageMemoryRequirements2
-> Ptr VkSparseImageMemoryRequirements2
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageMemoryRequirements2
x) (Int
16))
{-# LINE 1442 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageMemoryRequirements2
-> IO
(FieldType "memoryRequirements" VkSparseImageMemoryRequirements2)
readField Ptr VkSparseImageMemoryRequirements2
p
= Ptr VkSparseImageMemoryRequirements2
-> Int -> IO VkSparseImageMemoryRequirements
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageMemoryRequirements2
p (Int
16)
{-# LINE 1446 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "memoryRequirements" VkSparseImageMemoryRequirements2
where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageMemoryRequirements2
-> FieldType "memoryRequirements" VkSparseImageMemoryRequirements2
-> IO ()
writeField Ptr VkSparseImageMemoryRequirements2
p
= Ptr VkSparseImageMemoryRequirements2
-> Int -> VkSparseImageMemoryRequirements -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageMemoryRequirements2
p (Int
16)
{-# LINE 1453 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance Show VkSparseImageMemoryRequirements2 where
showsPrec :: Int -> VkSparseImageMemoryRequirements2 -> ShowS
showsPrec Int
d VkSparseImageMemoryRequirements2
x
= String -> ShowS
showString String
"VkSparseImageMemoryRequirements2 {" 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 (VkSparseImageMemoryRequirements2
-> FieldType "sType" VkSparseImageMemoryRequirements2
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkSparseImageMemoryRequirements2
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 (VkSparseImageMemoryRequirements2
-> FieldType "pNext" VkSparseImageMemoryRequirements2
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkSparseImageMemoryRequirements2
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 -> VkSparseImageMemoryRequirements -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageMemoryRequirements2
-> FieldType "memoryRequirements" VkSparseImageMemoryRequirements2
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"memoryRequirements" VkSparseImageMemoryRequirements2
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
type VkSparseImageMemoryRequirements2KHR =
VkSparseImageMemoryRequirements2
data VkSparseImageOpaqueMemoryBindInfo = VkSparseImageOpaqueMemoryBindInfo# Addr#
ByteArray#
instance Eq VkSparseImageOpaqueMemoryBindInfo where
(VkSparseImageOpaqueMemoryBindInfo# Addr#
a ByteArray#
_) == :: VkSparseImageOpaqueMemoryBindInfo
-> VkSparseImageOpaqueMemoryBindInfo -> Bool
==
x :: VkSparseImageOpaqueMemoryBindInfo
x@(VkSparseImageOpaqueMemoryBindInfo# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageOpaqueMemoryBindInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageOpaqueMemoryBindInfo
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSparseImageOpaqueMemoryBindInfo where
(VkSparseImageOpaqueMemoryBindInfo# Addr#
a ByteArray#
_) compare :: VkSparseImageOpaqueMemoryBindInfo
-> VkSparseImageOpaqueMemoryBindInfo -> Ordering
`compare`
x :: VkSparseImageOpaqueMemoryBindInfo
x@(VkSparseImageOpaqueMemoryBindInfo# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseImageOpaqueMemoryBindInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseImageOpaqueMemoryBindInfo
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSparseImageOpaqueMemoryBindInfo where
sizeOf :: VkSparseImageOpaqueMemoryBindInfo -> Int
sizeOf ~VkSparseImageOpaqueMemoryBindInfo
_ = (Int
24)
{-# LINE 1496 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSparseImageOpaqueMemoryBindInfo -> Int
alignment ~VkSparseImageOpaqueMemoryBindInfo
_
= Int
8
{-# LINE 1500 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSparseImageOpaqueMemoryBindInfo
-> IO VkSparseImageOpaqueMemoryBindInfo
peek = Ptr VkSparseImageOpaqueMemoryBindInfo
-> IO VkSparseImageOpaqueMemoryBindInfo
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSparseImageOpaqueMemoryBindInfo
-> VkSparseImageOpaqueMemoryBindInfo -> IO ()
poke = Ptr VkSparseImageOpaqueMemoryBindInfo
-> VkSparseImageOpaqueMemoryBindInfo -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSparseImageOpaqueMemoryBindInfo where
unsafeAddr :: VkSparseImageOpaqueMemoryBindInfo -> Addr#
unsafeAddr (VkSparseImageOpaqueMemoryBindInfo# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSparseImageOpaqueMemoryBindInfo -> ByteArray#
unsafeByteArray (VkSparseImageOpaqueMemoryBindInfo# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSparseImageOpaqueMemoryBindInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSparseImageOpaqueMemoryBindInfo
VkSparseImageOpaqueMemoryBindInfo#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSparseImageOpaqueMemoryBindInfo where
type StructFields VkSparseImageOpaqueMemoryBindInfo =
'["image", "bindCount", "pBinds"]
type CUnionType VkSparseImageOpaqueMemoryBindInfo = 'False
type ReturnedOnly VkSparseImageOpaqueMemoryBindInfo = 'False
type StructExtends VkSparseImageOpaqueMemoryBindInfo = '[]
instance {-# OVERLAPPING #-}
HasField "image" VkSparseImageOpaqueMemoryBindInfo where
type FieldType "image" VkSparseImageOpaqueMemoryBindInfo = VkImage
type FieldOptional "image" VkSparseImageOpaqueMemoryBindInfo =
'False
type FieldOffset "image" VkSparseImageOpaqueMemoryBindInfo =
(0)
{-# LINE 1537 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "image" VkSparseImageOpaqueMemoryBindInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 1546 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "image" VkSparseImageOpaqueMemoryBindInfo where
{-# NOINLINE getField #-}
getField :: VkSparseImageOpaqueMemoryBindInfo
-> FieldType "image" VkSparseImageOpaqueMemoryBindInfo
getField VkSparseImageOpaqueMemoryBindInfo
x
= IO VkImage -> VkImage
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageOpaqueMemoryBindInfo -> Int -> IO VkImage
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageOpaqueMemoryBindInfo
-> Ptr VkSparseImageOpaqueMemoryBindInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageOpaqueMemoryBindInfo
x) (Int
0))
{-# LINE 1553 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageOpaqueMemoryBindInfo
-> IO (FieldType "image" VkSparseImageOpaqueMemoryBindInfo)
readField Ptr VkSparseImageOpaqueMemoryBindInfo
p
= Ptr VkSparseImageOpaqueMemoryBindInfo -> Int -> IO VkImage
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageOpaqueMemoryBindInfo
p (Int
0)
{-# LINE 1557 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "image" VkSparseImageOpaqueMemoryBindInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageOpaqueMemoryBindInfo
-> FieldType "image" VkSparseImageOpaqueMemoryBindInfo -> IO ()
writeField Ptr VkSparseImageOpaqueMemoryBindInfo
p
= Ptr VkSparseImageOpaqueMemoryBindInfo -> Int -> VkImage -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageOpaqueMemoryBindInfo
p (Int
0)
{-# LINE 1563 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "bindCount" VkSparseImageOpaqueMemoryBindInfo where
type FieldType "bindCount" VkSparseImageOpaqueMemoryBindInfo =
Word32
type FieldOptional "bindCount" VkSparseImageOpaqueMemoryBindInfo =
'False
type FieldOffset "bindCount" VkSparseImageOpaqueMemoryBindInfo =
(8)
{-# LINE 1572 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "bindCount" VkSparseImageOpaqueMemoryBindInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 1581 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "bindCount" VkSparseImageOpaqueMemoryBindInfo where
{-# NOINLINE getField #-}
getField :: VkSparseImageOpaqueMemoryBindInfo
-> FieldType "bindCount" VkSparseImageOpaqueMemoryBindInfo
getField VkSparseImageOpaqueMemoryBindInfo
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageOpaqueMemoryBindInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageOpaqueMemoryBindInfo
-> Ptr VkSparseImageOpaqueMemoryBindInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageOpaqueMemoryBindInfo
x) (Int
8))
{-# LINE 1588 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageOpaqueMemoryBindInfo
-> IO (FieldType "bindCount" VkSparseImageOpaqueMemoryBindInfo)
readField Ptr VkSparseImageOpaqueMemoryBindInfo
p
= Ptr VkSparseImageOpaqueMemoryBindInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageOpaqueMemoryBindInfo
p (Int
8)
{-# LINE 1592 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "bindCount" VkSparseImageOpaqueMemoryBindInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageOpaqueMemoryBindInfo
-> FieldType "bindCount" VkSparseImageOpaqueMemoryBindInfo -> IO ()
writeField Ptr VkSparseImageOpaqueMemoryBindInfo
p
= Ptr VkSparseImageOpaqueMemoryBindInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageOpaqueMemoryBindInfo
p (Int
8)
{-# LINE 1598 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pBinds" VkSparseImageOpaqueMemoryBindInfo where
type FieldType "pBinds" VkSparseImageOpaqueMemoryBindInfo =
Ptr VkSparseMemoryBind
type FieldOptional "pBinds" VkSparseImageOpaqueMemoryBindInfo =
'False
type FieldOffset "pBinds" VkSparseImageOpaqueMemoryBindInfo =
(16)
{-# LINE 1607 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "pBinds" VkSparseImageOpaqueMemoryBindInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 1616 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pBinds" VkSparseImageOpaqueMemoryBindInfo where
{-# NOINLINE getField #-}
getField :: VkSparseImageOpaqueMemoryBindInfo
-> FieldType "pBinds" VkSparseImageOpaqueMemoryBindInfo
getField VkSparseImageOpaqueMemoryBindInfo
x
= IO (Ptr VkSparseMemoryBind) -> Ptr VkSparseMemoryBind
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseImageOpaqueMemoryBindInfo
-> Int -> IO (Ptr VkSparseMemoryBind)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseImageOpaqueMemoryBindInfo
-> Ptr VkSparseImageOpaqueMemoryBindInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseImageOpaqueMemoryBindInfo
x) (Int
16))
{-# LINE 1623 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseImageOpaqueMemoryBindInfo
-> IO (FieldType "pBinds" VkSparseImageOpaqueMemoryBindInfo)
readField Ptr VkSparseImageOpaqueMemoryBindInfo
p
= Ptr VkSparseImageOpaqueMemoryBindInfo
-> Int -> IO (Ptr VkSparseMemoryBind)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseImageOpaqueMemoryBindInfo
p (Int
16)
{-# LINE 1627 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pBinds" VkSparseImageOpaqueMemoryBindInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseImageOpaqueMemoryBindInfo
-> FieldType "pBinds" VkSparseImageOpaqueMemoryBindInfo -> IO ()
writeField Ptr VkSparseImageOpaqueMemoryBindInfo
p
= Ptr VkSparseImageOpaqueMemoryBindInfo
-> Int -> Ptr VkSparseMemoryBind -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseImageOpaqueMemoryBindInfo
p (Int
16)
{-# LINE 1633 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance Show VkSparseImageOpaqueMemoryBindInfo where
showsPrec :: Int -> VkSparseImageOpaqueMemoryBindInfo -> ShowS
showsPrec Int
d VkSparseImageOpaqueMemoryBindInfo
x
= String -> ShowS
showString String
"VkSparseImageOpaqueMemoryBindInfo {" 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 (VkSparseImageOpaqueMemoryBindInfo
-> FieldType "image" VkSparseImageOpaqueMemoryBindInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"image" VkSparseImageOpaqueMemoryBindInfo
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
"bindCount = " 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 (VkSparseImageOpaqueMemoryBindInfo
-> FieldType "bindCount" VkSparseImageOpaqueMemoryBindInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"bindCount" VkSparseImageOpaqueMemoryBindInfo
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
"pBinds = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> Ptr VkSparseMemoryBind -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseImageOpaqueMemoryBindInfo
-> FieldType "pBinds" VkSparseImageOpaqueMemoryBindInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pBinds" VkSparseImageOpaqueMemoryBindInfo
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkSparseMemoryBind = VkSparseMemoryBind# Addr# ByteArray#
instance Eq VkSparseMemoryBind where
(VkSparseMemoryBind# Addr#
a ByteArray#
_) == :: VkSparseMemoryBind -> VkSparseMemoryBind -> Bool
== x :: VkSparseMemoryBind
x@(VkSparseMemoryBind# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseMemoryBind -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseMemoryBind
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSparseMemoryBind where
(VkSparseMemoryBind# Addr#
a ByteArray#
_) compare :: VkSparseMemoryBind -> VkSparseMemoryBind -> Ordering
`compare` x :: VkSparseMemoryBind
x@(VkSparseMemoryBind# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSparseMemoryBind -> Int
forall a. Storable a => a -> Int
sizeOf VkSparseMemoryBind
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSparseMemoryBind where
sizeOf :: VkSparseMemoryBind -> Int
sizeOf ~VkSparseMemoryBind
_ = (Int
40)
{-# LINE 1671 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSparseMemoryBind -> Int
alignment ~VkSparseMemoryBind
_ = Int
8
{-# LINE 1674 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSparseMemoryBind -> IO VkSparseMemoryBind
peek = Ptr VkSparseMemoryBind -> IO VkSparseMemoryBind
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSparseMemoryBind -> VkSparseMemoryBind -> IO ()
poke = Ptr VkSparseMemoryBind -> VkSparseMemoryBind -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSparseMemoryBind where
unsafeAddr :: VkSparseMemoryBind -> Addr#
unsafeAddr (VkSparseMemoryBind# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSparseMemoryBind -> ByteArray#
unsafeByteArray (VkSparseMemoryBind# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSparseMemoryBind
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSparseMemoryBind
VkSparseMemoryBind# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSparseMemoryBind where
type StructFields VkSparseMemoryBind =
'["resourceOffset", "size", "memory", "memoryOffset", "flags"]
type CUnionType VkSparseMemoryBind = 'False
type ReturnedOnly VkSparseMemoryBind = 'False
type StructExtends VkSparseMemoryBind = '[]
instance {-# OVERLAPPING #-}
HasField "resourceOffset" VkSparseMemoryBind where
type FieldType "resourceOffset" VkSparseMemoryBind = VkDeviceSize
type FieldOptional "resourceOffset" VkSparseMemoryBind = 'False
type FieldOffset "resourceOffset" VkSparseMemoryBind =
(0)
{-# LINE 1708 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "resourceOffset" VkSparseMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 1716 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "resourceOffset" VkSparseMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseMemoryBind -> FieldType "resourceOffset" VkSparseMemoryBind
getField VkSparseMemoryBind
x
= IO VkDeviceSize -> VkDeviceSize
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseMemoryBind -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseMemoryBind -> Ptr VkSparseMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseMemoryBind
x) (Int
0))
{-# LINE 1723 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseMemoryBind
-> IO (FieldType "resourceOffset" VkSparseMemoryBind)
readField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseMemoryBind
p (Int
0)
{-# LINE 1727 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "resourceOffset" VkSparseMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseMemoryBind
-> FieldType "resourceOffset" VkSparseMemoryBind -> IO ()
writeField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseMemoryBind
p (Int
0)
{-# LINE 1733 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-} HasField "size" VkSparseMemoryBind
where
type FieldType "size" VkSparseMemoryBind = VkDeviceSize
type FieldOptional "size" VkSparseMemoryBind = 'False
type FieldOffset "size" VkSparseMemoryBind =
(8)
{-# LINE 1740 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "size" VkSparseMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 1747 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-} CanReadField "size" VkSparseMemoryBind
where
{-# NOINLINE getField #-}
getField :: VkSparseMemoryBind -> FieldType "size" VkSparseMemoryBind
getField VkSparseMemoryBind
x
= IO VkDeviceSize -> VkDeviceSize
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseMemoryBind -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseMemoryBind -> Ptr VkSparseMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseMemoryBind
x) (Int
8))
{-# LINE 1754 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseMemoryBind -> IO (FieldType "size" VkSparseMemoryBind)
readField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseMemoryBind
p (Int
8)
{-# LINE 1758 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "size" VkSparseMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseMemoryBind
-> FieldType "size" VkSparseMemoryBind -> IO ()
writeField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseMemoryBind
p (Int
8)
{-# LINE 1764 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-} HasField "memory" VkSparseMemoryBind
where
type FieldType "memory" VkSparseMemoryBind = VkDeviceMemory
type FieldOptional "memory" VkSparseMemoryBind = 'True
type FieldOffset "memory" VkSparseMemoryBind =
(16)
{-# LINE 1771 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "memory" VkSparseMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
16)
{-# LINE 1778 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "memory" VkSparseMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseMemoryBind -> FieldType "memory" VkSparseMemoryBind
getField VkSparseMemoryBind
x
= IO VkDeviceMemory -> VkDeviceMemory
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseMemoryBind -> Int -> IO VkDeviceMemory
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseMemoryBind -> Ptr VkSparseMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseMemoryBind
x) (Int
16))
{-# LINE 1785 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseMemoryBind
-> IO (FieldType "memory" VkSparseMemoryBind)
readField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> IO VkDeviceMemory
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseMemoryBind
p (Int
16)
{-# LINE 1789 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "memory" VkSparseMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseMemoryBind
-> FieldType "memory" VkSparseMemoryBind -> IO ()
writeField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> VkDeviceMemory -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseMemoryBind
p (Int
16)
{-# LINE 1795 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "memoryOffset" VkSparseMemoryBind where
type FieldType "memoryOffset" VkSparseMemoryBind = VkDeviceSize
type FieldOptional "memoryOffset" VkSparseMemoryBind = 'False
type FieldOffset "memoryOffset" VkSparseMemoryBind =
(24)
{-# LINE 1802 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "memoryOffset" VkSparseMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
24)
{-# LINE 1810 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "memoryOffset" VkSparseMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseMemoryBind -> FieldType "memoryOffset" VkSparseMemoryBind
getField VkSparseMemoryBind
x
= IO VkDeviceSize -> VkDeviceSize
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseMemoryBind -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseMemoryBind -> Ptr VkSparseMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseMemoryBind
x) (Int
24))
{-# LINE 1817 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseMemoryBind
-> IO (FieldType "memoryOffset" VkSparseMemoryBind)
readField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> IO VkDeviceSize
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseMemoryBind
p (Int
24)
{-# LINE 1821 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "memoryOffset" VkSparseMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseMemoryBind
-> FieldType "memoryOffset" VkSparseMemoryBind -> IO ()
writeField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> VkDeviceSize -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseMemoryBind
p (Int
24)
{-# LINE 1827 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-} HasField "flags" VkSparseMemoryBind
where
type FieldType "flags" VkSparseMemoryBind = VkSparseMemoryBindFlags
type FieldOptional "flags" VkSparseMemoryBind = 'True
type FieldOffset "flags" VkSparseMemoryBind =
(32)
{-# LINE 1834 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
type FieldIsArray "flags" VkSparseMemoryBind = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
32)
{-# LINE 1841 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "flags" VkSparseMemoryBind where
{-# NOINLINE getField #-}
getField :: VkSparseMemoryBind -> FieldType "flags" VkSparseMemoryBind
getField VkSparseMemoryBind
x
= IO VkSparseMemoryBindFlags -> VkSparseMemoryBindFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSparseMemoryBind -> Int -> IO VkSparseMemoryBindFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSparseMemoryBind -> Ptr VkSparseMemoryBind
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSparseMemoryBind
x) (Int
32))
{-# LINE 1848 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSparseMemoryBind -> IO (FieldType "flags" VkSparseMemoryBind)
readField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> IO VkSparseMemoryBindFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSparseMemoryBind
p (Int
32)
{-# LINE 1852 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "flags" VkSparseMemoryBind where
{-# INLINE writeField #-}
writeField :: Ptr VkSparseMemoryBind
-> FieldType "flags" VkSparseMemoryBind -> IO ()
writeField Ptr VkSparseMemoryBind
p
= Ptr VkSparseMemoryBind -> Int -> VkSparseMemoryBindFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSparseMemoryBind
p (Int
32)
{-# LINE 1858 "src-gen/Graphics/Vulkan/Types/Struct/Sparse.hsc" #-}
instance Show VkSparseMemoryBind where
showsPrec :: Int -> VkSparseMemoryBind -> ShowS
showsPrec Int
d VkSparseMemoryBind
x
= String -> ShowS
showString String
"VkSparseMemoryBind {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
"resourceOffset = " 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 (VkSparseMemoryBind -> FieldType "resourceOffset" VkSparseMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"resourceOffset" VkSparseMemoryBind
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
"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 (VkSparseMemoryBind -> FieldType "size" VkSparseMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"size" VkSparseMemoryBind
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 (VkSparseMemoryBind -> FieldType "memory" VkSparseMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"memory" VkSparseMemoryBind
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
"memoryOffset = " 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 (VkSparseMemoryBind -> FieldType "memoryOffset" VkSparseMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"memoryOffset" VkSparseMemoryBind
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 -> VkSparseMemoryBindFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSparseMemoryBind -> FieldType "flags" VkSparseMemoryBind
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkSparseMemoryBind
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'