{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Vulkan.Types.Struct.FormatProperties
(VkFormatProperties(..), VkFormatProperties2(..),
VkFormatProperties2KHR)
where
import Foreign.Storable (Storable (..))
import GHC.Base (Addr#, ByteArray#,
byteArrayContents#,
plusAddr#)
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.Enum.Format (VkFormatFeatureFlags)
import Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import System.IO.Unsafe (unsafeDupablePerformIO)
data VkFormatProperties = VkFormatProperties# Addr# ByteArray#
instance Eq VkFormatProperties where
(VkFormatProperties# Addr#
a ByteArray#
_) == :: VkFormatProperties -> VkFormatProperties -> Bool
== x :: VkFormatProperties
x@(VkFormatProperties# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkFormatProperties -> Int
forall a. Storable a => a -> Int
sizeOf VkFormatProperties
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkFormatProperties where
(VkFormatProperties# Addr#
a ByteArray#
_) compare :: VkFormatProperties -> VkFormatProperties -> Ordering
`compare` x :: VkFormatProperties
x@(VkFormatProperties# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkFormatProperties -> Int
forall a. Storable a => a -> Int
sizeOf VkFormatProperties
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkFormatProperties where
sizeOf :: VkFormatProperties -> Int
sizeOf ~VkFormatProperties
_ = (Int
12)
{-# LINE 47 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkFormatProperties -> Int
alignment ~VkFormatProperties
_ = Int
4
{-# LINE 50 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkFormatProperties -> IO VkFormatProperties
peek = Ptr VkFormatProperties -> IO VkFormatProperties
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkFormatProperties -> VkFormatProperties -> IO ()
poke = Ptr VkFormatProperties -> VkFormatProperties -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkFormatProperties where
unsafeAddr :: VkFormatProperties -> Addr#
unsafeAddr (VkFormatProperties# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkFormatProperties -> ByteArray#
unsafeByteArray (VkFormatProperties# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkFormatProperties
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkFormatProperties
VkFormatProperties# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkFormatProperties where
type StructFields VkFormatProperties =
'["linearTilingFeatures", "optimalTilingFeatures",
"bufferFeatures"]
type CUnionType VkFormatProperties = 'False
type ReturnedOnly VkFormatProperties = 'True
type StructExtends VkFormatProperties = '[]
instance {-# OVERLAPPING #-}
HasField "linearTilingFeatures" VkFormatProperties where
type FieldType "linearTilingFeatures" VkFormatProperties =
VkFormatFeatureFlags
type FieldOptional "linearTilingFeatures" VkFormatProperties =
'True
type FieldOffset "linearTilingFeatures" VkFormatProperties =
(0)
{-# LINE 87 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
type FieldIsArray "linearTilingFeatures" VkFormatProperties =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 96 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "linearTilingFeatures" VkFormatProperties where
{-# NOINLINE getField #-}
getField :: VkFormatProperties
-> FieldType "linearTilingFeatures" VkFormatProperties
getField VkFormatProperties
x
= IO VkFormatFeatureFlags -> VkFormatFeatureFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkFormatProperties -> Int -> IO VkFormatFeatureFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkFormatProperties -> Ptr VkFormatProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkFormatProperties
x) (Int
0))
{-# LINE 103 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkFormatProperties
-> IO (FieldType "linearTilingFeatures" VkFormatProperties)
readField Ptr VkFormatProperties
p
= Ptr VkFormatProperties -> Int -> IO VkFormatFeatureFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkFormatProperties
p (Int
0)
{-# LINE 107 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "linearTilingFeatures" VkFormatProperties where
{-# INLINE writeField #-}
writeField :: Ptr VkFormatProperties
-> FieldType "linearTilingFeatures" VkFormatProperties -> IO ()
writeField Ptr VkFormatProperties
p
= Ptr VkFormatProperties -> Int -> VkFormatFeatureFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkFormatProperties
p (Int
0)
{-# LINE 113 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "optimalTilingFeatures" VkFormatProperties where
type FieldType "optimalTilingFeatures" VkFormatProperties =
VkFormatFeatureFlags
type FieldOptional "optimalTilingFeatures" VkFormatProperties =
'True
type FieldOffset "optimalTilingFeatures" VkFormatProperties =
(4)
{-# LINE 122 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
type FieldIsArray "optimalTilingFeatures" VkFormatProperties =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
4)
{-# LINE 131 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "optimalTilingFeatures" VkFormatProperties where
{-# NOINLINE getField #-}
getField :: VkFormatProperties
-> FieldType "optimalTilingFeatures" VkFormatProperties
getField VkFormatProperties
x
= IO VkFormatFeatureFlags -> VkFormatFeatureFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkFormatProperties -> Int -> IO VkFormatFeatureFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkFormatProperties -> Ptr VkFormatProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkFormatProperties
x) (Int
4))
{-# LINE 138 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkFormatProperties
-> IO (FieldType "optimalTilingFeatures" VkFormatProperties)
readField Ptr VkFormatProperties
p
= Ptr VkFormatProperties -> Int -> IO VkFormatFeatureFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkFormatProperties
p (Int
4)
{-# LINE 142 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "optimalTilingFeatures" VkFormatProperties where
{-# INLINE writeField #-}
writeField :: Ptr VkFormatProperties
-> FieldType "optimalTilingFeatures" VkFormatProperties -> IO ()
writeField Ptr VkFormatProperties
p
= Ptr VkFormatProperties -> Int -> VkFormatFeatureFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkFormatProperties
p (Int
4)
{-# LINE 148 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "bufferFeatures" VkFormatProperties where
type FieldType "bufferFeatures" VkFormatProperties =
VkFormatFeatureFlags
type FieldOptional "bufferFeatures" VkFormatProperties = 'True
type FieldOffset "bufferFeatures" VkFormatProperties =
(8)
{-# LINE 156 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
type FieldIsArray "bufferFeatures" VkFormatProperties = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 164 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "bufferFeatures" VkFormatProperties where
{-# NOINLINE getField #-}
getField :: VkFormatProperties -> FieldType "bufferFeatures" VkFormatProperties
getField VkFormatProperties
x
= IO VkFormatFeatureFlags -> VkFormatFeatureFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkFormatProperties -> Int -> IO VkFormatFeatureFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkFormatProperties -> Ptr VkFormatProperties
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkFormatProperties
x) (Int
8))
{-# LINE 171 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkFormatProperties
-> IO (FieldType "bufferFeatures" VkFormatProperties)
readField Ptr VkFormatProperties
p
= Ptr VkFormatProperties -> Int -> IO VkFormatFeatureFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkFormatProperties
p (Int
8)
{-# LINE 175 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "bufferFeatures" VkFormatProperties where
{-# INLINE writeField #-}
writeField :: Ptr VkFormatProperties
-> FieldType "bufferFeatures" VkFormatProperties -> IO ()
writeField Ptr VkFormatProperties
p
= Ptr VkFormatProperties -> Int -> VkFormatFeatureFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkFormatProperties
p (Int
8)
{-# LINE 181 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance Show VkFormatProperties where
showsPrec :: Int -> VkFormatProperties -> ShowS
showsPrec Int
d VkFormatProperties
x
= String -> ShowS
showString String
"VkFormatProperties {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
"linearTilingFeatures = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkFormatFeatureFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkFormatProperties
-> FieldType "linearTilingFeatures" VkFormatProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"linearTilingFeatures" VkFormatProperties
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
"optimalTilingFeatures = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkFormatFeatureFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkFormatProperties
-> FieldType "optimalTilingFeatures" VkFormatProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"optimalTilingFeatures" VkFormatProperties
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
"bufferFeatures = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkFormatFeatureFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkFormatProperties -> FieldType "bufferFeatures" VkFormatProperties
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"bufferFeatures" VkFormatProperties
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkFormatProperties2 = VkFormatProperties2# Addr# ByteArray#
instance Eq VkFormatProperties2 where
(VkFormatProperties2# Addr#
a ByteArray#
_) == :: VkFormatProperties2 -> VkFormatProperties2 -> Bool
== x :: VkFormatProperties2
x@(VkFormatProperties2# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkFormatProperties2 -> Int
forall a. Storable a => a -> Int
sizeOf VkFormatProperties2
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkFormatProperties2 where
(VkFormatProperties2# Addr#
a ByteArray#
_) compare :: VkFormatProperties2 -> VkFormatProperties2 -> Ordering
`compare` x :: VkFormatProperties2
x@(VkFormatProperties2# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkFormatProperties2 -> Int
forall a. Storable a => a -> Int
sizeOf VkFormatProperties2
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkFormatProperties2 where
sizeOf :: VkFormatProperties2 -> Int
sizeOf ~VkFormatProperties2
_ = (Int
32)
{-# LINE 217 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkFormatProperties2 -> Int
alignment ~VkFormatProperties2
_ = Int
8
{-# LINE 220 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkFormatProperties2 -> IO VkFormatProperties2
peek = Ptr VkFormatProperties2 -> IO VkFormatProperties2
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkFormatProperties2 -> VkFormatProperties2 -> IO ()
poke = Ptr VkFormatProperties2 -> VkFormatProperties2 -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkFormatProperties2 where
unsafeAddr :: VkFormatProperties2 -> Addr#
unsafeAddr (VkFormatProperties2# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkFormatProperties2 -> ByteArray#
unsafeByteArray (VkFormatProperties2# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkFormatProperties2
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkFormatProperties2
VkFormatProperties2# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkFormatProperties2 where
type StructFields VkFormatProperties2 =
'["sType", "pNext", "formatProperties"]
type CUnionType VkFormatProperties2 = 'False
type ReturnedOnly VkFormatProperties2 = 'True
type StructExtends VkFormatProperties2 = '[]
instance {-# OVERLAPPING #-} HasField "sType" VkFormatProperties2
where
type FieldType "sType" VkFormatProperties2 = VkStructureType
type FieldOptional "sType" VkFormatProperties2 = 'False
type FieldOffset "sType" VkFormatProperties2 =
(0)
{-# LINE 254 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
type FieldIsArray "sType" VkFormatProperties2 = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 261 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkFormatProperties2 where
{-# NOINLINE getField #-}
getField :: VkFormatProperties2 -> FieldType "sType" VkFormatProperties2
getField VkFormatProperties2
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkFormatProperties2 -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkFormatProperties2 -> Ptr VkFormatProperties2
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkFormatProperties2
x) (Int
0))
{-# LINE 268 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkFormatProperties2
-> IO (FieldType "sType" VkFormatProperties2)
readField Ptr VkFormatProperties2
p
= Ptr VkFormatProperties2 -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkFormatProperties2
p (Int
0)
{-# LINE 272 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkFormatProperties2 where
{-# INLINE writeField #-}
writeField :: Ptr VkFormatProperties2
-> FieldType "sType" VkFormatProperties2 -> IO ()
writeField Ptr VkFormatProperties2
p
= Ptr VkFormatProperties2 -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkFormatProperties2
p (Int
0)
{-# LINE 278 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-} HasField "pNext" VkFormatProperties2
where
type FieldType "pNext" VkFormatProperties2 = Ptr Void
type FieldOptional "pNext" VkFormatProperties2 = 'False
type FieldOffset "pNext" VkFormatProperties2 =
(8)
{-# LINE 285 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
type FieldIsArray "pNext" VkFormatProperties2 = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 292 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkFormatProperties2 where
{-# NOINLINE getField #-}
getField :: VkFormatProperties2 -> FieldType "pNext" VkFormatProperties2
getField VkFormatProperties2
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkFormatProperties2 -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkFormatProperties2 -> Ptr VkFormatProperties2
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkFormatProperties2
x) (Int
8))
{-# LINE 299 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkFormatProperties2
-> IO (FieldType "pNext" VkFormatProperties2)
readField Ptr VkFormatProperties2
p
= Ptr VkFormatProperties2 -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkFormatProperties2
p (Int
8)
{-# LINE 303 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkFormatProperties2 where
{-# INLINE writeField #-}
writeField :: Ptr VkFormatProperties2
-> FieldType "pNext" VkFormatProperties2 -> IO ()
writeField Ptr VkFormatProperties2
p
= Ptr VkFormatProperties2 -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkFormatProperties2
p (Int
8)
{-# LINE 309 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "formatProperties" VkFormatProperties2 where
type FieldType "formatProperties" VkFormatProperties2 =
VkFormatProperties
type FieldOptional "formatProperties" VkFormatProperties2 = 'False
type FieldOffset "formatProperties" VkFormatProperties2 =
(16)
{-# LINE 317 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
type FieldIsArray "formatProperties" VkFormatProperties2 = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 325 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "formatProperties" VkFormatProperties2 where
{-# NOINLINE getField #-}
getField :: VkFormatProperties2
-> FieldType "formatProperties" VkFormatProperties2
getField VkFormatProperties2
x
= IO VkFormatProperties -> VkFormatProperties
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkFormatProperties2 -> Int -> IO VkFormatProperties
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkFormatProperties2 -> Ptr VkFormatProperties2
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkFormatProperties2
x) (Int
16))
{-# LINE 332 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkFormatProperties2
-> IO (FieldType "formatProperties" VkFormatProperties2)
readField Ptr VkFormatProperties2
p
= Ptr VkFormatProperties2 -> Int -> IO VkFormatProperties
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkFormatProperties2
p (Int
16)
{-# LINE 336 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "formatProperties" VkFormatProperties2 where
{-# INLINE writeField #-}
writeField :: Ptr VkFormatProperties2
-> FieldType "formatProperties" VkFormatProperties2 -> IO ()
writeField Ptr VkFormatProperties2
p
= Ptr VkFormatProperties2 -> Int -> VkFormatProperties -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkFormatProperties2
p (Int
16)
{-# LINE 342 "src-gen/Graphics/Vulkan/Types/Struct/FormatProperties.hsc" #-}
instance Show VkFormatProperties2 where
showsPrec :: Int -> VkFormatProperties2 -> ShowS
showsPrec Int
d VkFormatProperties2
x
= String -> ShowS
showString String
"VkFormatProperties2 {" 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 (VkFormatProperties2 -> FieldType "sType" VkFormatProperties2
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkFormatProperties2
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 (VkFormatProperties2 -> FieldType "pNext" VkFormatProperties2
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkFormatProperties2
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
"formatProperties = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkFormatProperties -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkFormatProperties2
-> FieldType "formatProperties" VkFormatProperties2
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"formatProperties" VkFormatProperties2
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
type VkFormatProperties2KHR = VkFormatProperties2