{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Vulkan.Types.Struct.Attachment
(VkAttachmentDescription(..), VkAttachmentReference(..),
VkAttachmentSampleLocationsEXT(..))
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.Attachment (VkAttachmentDescriptionFlags,
VkAttachmentLoadOp,
VkAttachmentStoreOp)
import Graphics.Vulkan.Types.Enum.Format (VkFormat)
import Graphics.Vulkan.Types.Enum.Image (VkImageLayout)
import Graphics.Vulkan.Types.Enum.SampleCountFlags (VkSampleCountFlagBits)
import Graphics.Vulkan.Types.Struct.SampleLocation (VkSampleLocationsInfoEXT)
import System.IO.Unsafe (unsafeDupablePerformIO)
data VkAttachmentDescription = VkAttachmentDescription# Addr#
ByteArray#
instance Eq VkAttachmentDescription where
(VkAttachmentDescription# Addr#
a ByteArray#
_) == :: VkAttachmentDescription -> VkAttachmentDescription -> Bool
== x :: VkAttachmentDescription
x@(VkAttachmentDescription# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkAttachmentDescription -> Int
forall a. Storable a => a -> Int
sizeOf VkAttachmentDescription
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkAttachmentDescription where
(VkAttachmentDescription# Addr#
a ByteArray#
_) compare :: VkAttachmentDescription -> VkAttachmentDescription -> Ordering
`compare`
x :: VkAttachmentDescription
x@(VkAttachmentDescription# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkAttachmentDescription -> Int
forall a. Storable a => a -> Int
sizeOf VkAttachmentDescription
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkAttachmentDescription where
sizeOf :: VkAttachmentDescription -> Int
sizeOf ~VkAttachmentDescription
_ = (Int
36)
{-# LINE 59 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkAttachmentDescription -> Int
alignment ~VkAttachmentDescription
_ = Int
4
{-# LINE 62 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkAttachmentDescription -> IO VkAttachmentDescription
peek = Ptr VkAttachmentDescription -> IO VkAttachmentDescription
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkAttachmentDescription -> VkAttachmentDescription -> IO ()
poke = Ptr VkAttachmentDescription -> VkAttachmentDescription -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkAttachmentDescription where
unsafeAddr :: VkAttachmentDescription -> Addr#
unsafeAddr (VkAttachmentDescription# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkAttachmentDescription -> ByteArray#
unsafeByteArray (VkAttachmentDescription# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkAttachmentDescription
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkAttachmentDescription
VkAttachmentDescription# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkAttachmentDescription where
type StructFields VkAttachmentDescription =
'["flags", "format", "samples", "loadOp", "storeOp",
"stencilLoadOp", "stencilStoreOp", "initialLayout", "finalLayout"]
type CUnionType VkAttachmentDescription = 'False
type ReturnedOnly VkAttachmentDescription = 'False
type StructExtends VkAttachmentDescription = '[]
instance {-# OVERLAPPING #-}
HasField "flags" VkAttachmentDescription where
type FieldType "flags" VkAttachmentDescription =
VkAttachmentDescriptionFlags
type FieldOptional "flags" VkAttachmentDescription = 'True
type FieldOffset "flags" VkAttachmentDescription =
(0)
{-# LINE 98 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "flags" VkAttachmentDescription = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 105 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "flags" VkAttachmentDescription where
{-# NOINLINE getField #-}
getField :: VkAttachmentDescription
-> FieldType "flags" VkAttachmentDescription
getField VkAttachmentDescription
x
= IO VkAttachmentDescriptionFlags -> VkAttachmentDescriptionFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentDescription
-> Int -> IO VkAttachmentDescriptionFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentDescription -> Ptr VkAttachmentDescription
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentDescription
x) (Int
0))
{-# LINE 112 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentDescription
-> IO (FieldType "flags" VkAttachmentDescription)
readField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription
-> Int -> IO VkAttachmentDescriptionFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentDescription
p (Int
0)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "flags" VkAttachmentDescription where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentDescription
-> FieldType "flags" VkAttachmentDescription -> IO ()
writeField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription
-> Int -> VkAttachmentDescriptionFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentDescription
p (Int
0)
{-# LINE 122 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "format" VkAttachmentDescription where
type FieldType "format" VkAttachmentDescription = VkFormat
type FieldOptional "format" VkAttachmentDescription = 'False
type FieldOffset "format" VkAttachmentDescription =
(4)
{-# LINE 129 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "format" VkAttachmentDescription = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
4)
{-# LINE 136 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "format" VkAttachmentDescription where
{-# NOINLINE getField #-}
getField :: VkAttachmentDescription
-> FieldType "format" VkAttachmentDescription
getField VkAttachmentDescription
x
= IO VkFormat -> VkFormat
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentDescription -> Int -> IO VkFormat
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentDescription -> Ptr VkAttachmentDescription
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentDescription
x) (Int
4))
{-# LINE 143 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentDescription
-> IO (FieldType "format" VkAttachmentDescription)
readField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> IO VkFormat
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentDescription
p (Int
4)
{-# LINE 147 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "format" VkAttachmentDescription where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentDescription
-> FieldType "format" VkAttachmentDescription -> IO ()
writeField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> VkFormat -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentDescription
p (Int
4)
{-# LINE 153 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "samples" VkAttachmentDescription where
type FieldType "samples" VkAttachmentDescription =
VkSampleCountFlagBits
type FieldOptional "samples" VkAttachmentDescription = 'False
type FieldOffset "samples" VkAttachmentDescription =
(8)
{-# LINE 161 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "samples" VkAttachmentDescription = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 169 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "samples" VkAttachmentDescription where
{-# NOINLINE getField #-}
getField :: VkAttachmentDescription
-> FieldType "samples" VkAttachmentDescription
getField VkAttachmentDescription
x
= IO VkSampleCountFlagBits -> VkSampleCountFlagBits
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentDescription -> Int -> IO VkSampleCountFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentDescription -> Ptr VkAttachmentDescription
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentDescription
x) (Int
8))
{-# LINE 176 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentDescription
-> IO (FieldType "samples" VkAttachmentDescription)
readField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> IO VkSampleCountFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentDescription
p (Int
8)
{-# LINE 180 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "samples" VkAttachmentDescription where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentDescription
-> FieldType "samples" VkAttachmentDescription -> IO ()
writeField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription
-> Int -> VkSampleCountFlagBits -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentDescription
p (Int
8)
{-# LINE 186 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "loadOp" VkAttachmentDescription where
type FieldType "loadOp" VkAttachmentDescription =
VkAttachmentLoadOp
type FieldOptional "loadOp" VkAttachmentDescription = 'False
type FieldOffset "loadOp" VkAttachmentDescription =
(12)
{-# LINE 194 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "loadOp" VkAttachmentDescription = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
12)
{-# LINE 201 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "loadOp" VkAttachmentDescription where
{-# NOINLINE getField #-}
getField :: VkAttachmentDescription
-> FieldType "loadOp" VkAttachmentDescription
getField VkAttachmentDescription
x
= IO VkAttachmentLoadOp -> VkAttachmentLoadOp
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentDescription -> Int -> IO VkAttachmentLoadOp
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentDescription -> Ptr VkAttachmentDescription
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentDescription
x) (Int
12))
{-# LINE 208 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentDescription
-> IO (FieldType "loadOp" VkAttachmentDescription)
readField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> IO VkAttachmentLoadOp
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentDescription
p (Int
12)
{-# LINE 212 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "loadOp" VkAttachmentDescription where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentDescription
-> FieldType "loadOp" VkAttachmentDescription -> IO ()
writeField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> VkAttachmentLoadOp -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentDescription
p (Int
12)
{-# LINE 218 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "storeOp" VkAttachmentDescription where
type FieldType "storeOp" VkAttachmentDescription =
VkAttachmentStoreOp
type FieldOptional "storeOp" VkAttachmentDescription = 'False
type FieldOffset "storeOp" VkAttachmentDescription =
(16)
{-# LINE 226 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "storeOp" VkAttachmentDescription = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 234 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "storeOp" VkAttachmentDescription where
{-# NOINLINE getField #-}
getField :: VkAttachmentDescription
-> FieldType "storeOp" VkAttachmentDescription
getField VkAttachmentDescription
x
= IO VkAttachmentStoreOp -> VkAttachmentStoreOp
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentDescription -> Int -> IO VkAttachmentStoreOp
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentDescription -> Ptr VkAttachmentDescription
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentDescription
x) (Int
16))
{-# LINE 241 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentDescription
-> IO (FieldType "storeOp" VkAttachmentDescription)
readField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> IO VkAttachmentStoreOp
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentDescription
p (Int
16)
{-# LINE 245 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "storeOp" VkAttachmentDescription where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentDescription
-> FieldType "storeOp" VkAttachmentDescription -> IO ()
writeField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> VkAttachmentStoreOp -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentDescription
p (Int
16)
{-# LINE 251 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "stencilLoadOp" VkAttachmentDescription where
type FieldType "stencilLoadOp" VkAttachmentDescription =
VkAttachmentLoadOp
type FieldOptional "stencilLoadOp" VkAttachmentDescription = 'False
type FieldOffset "stencilLoadOp" VkAttachmentDescription =
(20)
{-# LINE 259 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "stencilLoadOp" VkAttachmentDescription = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
20)
{-# LINE 267 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "stencilLoadOp" VkAttachmentDescription where
{-# NOINLINE getField #-}
getField :: VkAttachmentDescription
-> FieldType "stencilLoadOp" VkAttachmentDescription
getField VkAttachmentDescription
x
= IO VkAttachmentLoadOp -> VkAttachmentLoadOp
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentDescription -> Int -> IO VkAttachmentLoadOp
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentDescription -> Ptr VkAttachmentDescription
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentDescription
x) (Int
20))
{-# LINE 274 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentDescription
-> IO (FieldType "stencilLoadOp" VkAttachmentDescription)
readField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> IO VkAttachmentLoadOp
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentDescription
p (Int
20)
{-# LINE 278 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "stencilLoadOp" VkAttachmentDescription where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentDescription
-> FieldType "stencilLoadOp" VkAttachmentDescription -> IO ()
writeField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> VkAttachmentLoadOp -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentDescription
p (Int
20)
{-# LINE 284 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "stencilStoreOp" VkAttachmentDescription where
type FieldType "stencilStoreOp" VkAttachmentDescription =
VkAttachmentStoreOp
type FieldOptional "stencilStoreOp" VkAttachmentDescription =
'False
type FieldOffset "stencilStoreOp" VkAttachmentDescription =
(24)
{-# LINE 293 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "stencilStoreOp" VkAttachmentDescription = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
24)
{-# LINE 301 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "stencilStoreOp" VkAttachmentDescription where
{-# NOINLINE getField #-}
getField :: VkAttachmentDescription
-> FieldType "stencilStoreOp" VkAttachmentDescription
getField VkAttachmentDescription
x
= IO VkAttachmentStoreOp -> VkAttachmentStoreOp
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentDescription -> Int -> IO VkAttachmentStoreOp
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentDescription -> Ptr VkAttachmentDescription
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentDescription
x) (Int
24))
{-# LINE 308 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentDescription
-> IO (FieldType "stencilStoreOp" VkAttachmentDescription)
readField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> IO VkAttachmentStoreOp
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentDescription
p (Int
24)
{-# LINE 312 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "stencilStoreOp" VkAttachmentDescription where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentDescription
-> FieldType "stencilStoreOp" VkAttachmentDescription -> IO ()
writeField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> VkAttachmentStoreOp -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentDescription
p (Int
24)
{-# LINE 318 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "initialLayout" VkAttachmentDescription where
type FieldType "initialLayout" VkAttachmentDescription =
VkImageLayout
type FieldOptional "initialLayout" VkAttachmentDescription = 'False
type FieldOffset "initialLayout" VkAttachmentDescription =
(28)
{-# LINE 326 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "initialLayout" VkAttachmentDescription = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
28)
{-# LINE 334 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "initialLayout" VkAttachmentDescription where
{-# NOINLINE getField #-}
getField :: VkAttachmentDescription
-> FieldType "initialLayout" VkAttachmentDescription
getField VkAttachmentDescription
x
= IO VkImageLayout -> VkImageLayout
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentDescription -> Int -> IO VkImageLayout
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentDescription -> Ptr VkAttachmentDescription
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentDescription
x) (Int
28))
{-# LINE 341 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentDescription
-> IO (FieldType "initialLayout" VkAttachmentDescription)
readField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> IO VkImageLayout
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentDescription
p (Int
28)
{-# LINE 345 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "initialLayout" VkAttachmentDescription where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentDescription
-> FieldType "initialLayout" VkAttachmentDescription -> IO ()
writeField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> VkImageLayout -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentDescription
p (Int
28)
{-# LINE 351 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "finalLayout" VkAttachmentDescription where
type FieldType "finalLayout" VkAttachmentDescription =
VkImageLayout
type FieldOptional "finalLayout" VkAttachmentDescription = 'False
type FieldOffset "finalLayout" VkAttachmentDescription =
(32)
{-# LINE 359 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "finalLayout" VkAttachmentDescription = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
32)
{-# LINE 367 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "finalLayout" VkAttachmentDescription where
{-# NOINLINE getField #-}
getField :: VkAttachmentDescription
-> FieldType "finalLayout" VkAttachmentDescription
getField VkAttachmentDescription
x
= IO VkImageLayout -> VkImageLayout
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentDescription -> Int -> IO VkImageLayout
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentDescription -> Ptr VkAttachmentDescription
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentDescription
x) (Int
32))
{-# LINE 374 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentDescription
-> IO (FieldType "finalLayout" VkAttachmentDescription)
readField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> IO VkImageLayout
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentDescription
p (Int
32)
{-# LINE 378 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "finalLayout" VkAttachmentDescription where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentDescription
-> FieldType "finalLayout" VkAttachmentDescription -> IO ()
writeField Ptr VkAttachmentDescription
p
= Ptr VkAttachmentDescription -> Int -> VkImageLayout -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentDescription
p (Int
32)
{-# LINE 384 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance Show VkAttachmentDescription where
showsPrec :: Int -> VkAttachmentDescription -> ShowS
showsPrec Int
d VkAttachmentDescription
x
= String -> ShowS
showString String
"VkAttachmentDescription {" 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 -> VkAttachmentDescriptionFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentDescription
-> FieldType "flags" VkAttachmentDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkAttachmentDescription
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
"format = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkFormat -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentDescription
-> FieldType "format" VkAttachmentDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"format" VkAttachmentDescription
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
"samples = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkSampleCountFlagBits -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentDescription
-> FieldType "samples" VkAttachmentDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"samples" VkAttachmentDescription
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
"loadOp = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkAttachmentLoadOp -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentDescription
-> FieldType "loadOp" VkAttachmentDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"loadOp" VkAttachmentDescription
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
"storeOp = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkAttachmentStoreOp -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentDescription
-> FieldType "storeOp" VkAttachmentDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"storeOp" VkAttachmentDescription
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
"stencilLoadOp = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkAttachmentLoadOp -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentDescription
-> FieldType "stencilLoadOp" VkAttachmentDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"stencilLoadOp" VkAttachmentDescription
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
"stencilStoreOp = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkAttachmentStoreOp -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentDescription
-> FieldType "stencilStoreOp" VkAttachmentDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"stencilStoreOp" VkAttachmentDescription
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
"initialLayout = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkImageLayout -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentDescription
-> FieldType "initialLayout" VkAttachmentDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"initialLayout" VkAttachmentDescription
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
"finalLayout = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkImageLayout -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d
(VkAttachmentDescription
-> FieldType "finalLayout" VkAttachmentDescription
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"finalLayout" VkAttachmentDescription
x)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkAttachmentReference = VkAttachmentReference# Addr#
ByteArray#
instance Eq VkAttachmentReference where
(VkAttachmentReference# Addr#
a ByteArray#
_) == :: VkAttachmentReference -> VkAttachmentReference -> Bool
== x :: VkAttachmentReference
x@(VkAttachmentReference# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkAttachmentReference -> Int
forall a. Storable a => a -> Int
sizeOf VkAttachmentReference
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkAttachmentReference where
(VkAttachmentReference# Addr#
a ByteArray#
_) compare :: VkAttachmentReference -> VkAttachmentReference -> Ordering
`compare`
x :: VkAttachmentReference
x@(VkAttachmentReference# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkAttachmentReference -> Int
forall a. Storable a => a -> Int
sizeOf VkAttachmentReference
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkAttachmentReference where
sizeOf :: VkAttachmentReference -> Int
sizeOf ~VkAttachmentReference
_ = (Int
8)
{-# LINE 441 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkAttachmentReference -> Int
alignment ~VkAttachmentReference
_ = Int
4
{-# LINE 444 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkAttachmentReference -> IO VkAttachmentReference
peek = Ptr VkAttachmentReference -> IO VkAttachmentReference
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkAttachmentReference -> VkAttachmentReference -> IO ()
poke = Ptr VkAttachmentReference -> VkAttachmentReference -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkAttachmentReference where
unsafeAddr :: VkAttachmentReference -> Addr#
unsafeAddr (VkAttachmentReference# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkAttachmentReference -> ByteArray#
unsafeByteArray (VkAttachmentReference# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkAttachmentReference
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkAttachmentReference
VkAttachmentReference# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkAttachmentReference where
type StructFields VkAttachmentReference = '["attachment", "layout"]
type CUnionType VkAttachmentReference = 'False
type ReturnedOnly VkAttachmentReference = 'False
type StructExtends VkAttachmentReference = '[]
instance {-# OVERLAPPING #-}
HasField "attachment" VkAttachmentReference where
type FieldType "attachment" VkAttachmentReference = Word32
type FieldOptional "attachment" VkAttachmentReference = 'False
type FieldOffset "attachment" VkAttachmentReference =
(0)
{-# LINE 477 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "attachment" VkAttachmentReference = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 485 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "attachment" VkAttachmentReference where
{-# NOINLINE getField #-}
getField :: VkAttachmentReference
-> FieldType "attachment" VkAttachmentReference
getField VkAttachmentReference
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentReference -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentReference -> Ptr VkAttachmentReference
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentReference
x) (Int
0))
{-# LINE 492 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentReference
-> IO (FieldType "attachment" VkAttachmentReference)
readField Ptr VkAttachmentReference
p
= Ptr VkAttachmentReference -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentReference
p (Int
0)
{-# LINE 496 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "attachment" VkAttachmentReference where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentReference
-> FieldType "attachment" VkAttachmentReference -> IO ()
writeField Ptr VkAttachmentReference
p
= Ptr VkAttachmentReference -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentReference
p (Int
0)
{-# LINE 502 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "layout" VkAttachmentReference where
type FieldType "layout" VkAttachmentReference = VkImageLayout
type FieldOptional "layout" VkAttachmentReference = 'False
type FieldOffset "layout" VkAttachmentReference =
(4)
{-# LINE 509 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "layout" VkAttachmentReference = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
4)
{-# LINE 516 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "layout" VkAttachmentReference where
{-# NOINLINE getField #-}
getField :: VkAttachmentReference -> FieldType "layout" VkAttachmentReference
getField VkAttachmentReference
x
= IO VkImageLayout -> VkImageLayout
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentReference -> Int -> IO VkImageLayout
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentReference -> Ptr VkAttachmentReference
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentReference
x) (Int
4))
{-# LINE 523 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentReference
-> IO (FieldType "layout" VkAttachmentReference)
readField Ptr VkAttachmentReference
p
= Ptr VkAttachmentReference -> Int -> IO VkImageLayout
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentReference
p (Int
4)
{-# LINE 527 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "layout" VkAttachmentReference where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentReference
-> FieldType "layout" VkAttachmentReference -> IO ()
writeField Ptr VkAttachmentReference
p
= Ptr VkAttachmentReference -> Int -> VkImageLayout -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentReference
p (Int
4)
{-# LINE 533 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance Show VkAttachmentReference where
showsPrec :: Int -> VkAttachmentReference -> ShowS
showsPrec Int
d VkAttachmentReference
x
= String -> ShowS
showString String
"VkAttachmentReference {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
"attachment = " 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 (VkAttachmentReference
-> FieldType "attachment" VkAttachmentReference
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"attachment" VkAttachmentReference
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
"layout = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkImageLayout -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentReference -> FieldType "layout" VkAttachmentReference
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"layout" VkAttachmentReference
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkAttachmentSampleLocationsEXT = VkAttachmentSampleLocationsEXT# Addr#
ByteArray#
instance Eq VkAttachmentSampleLocationsEXT where
(VkAttachmentSampleLocationsEXT# Addr#
a ByteArray#
_) == :: VkAttachmentSampleLocationsEXT
-> VkAttachmentSampleLocationsEXT -> Bool
==
x :: VkAttachmentSampleLocationsEXT
x@(VkAttachmentSampleLocationsEXT# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkAttachmentSampleLocationsEXT -> Int
forall a. Storable a => a -> Int
sizeOf VkAttachmentSampleLocationsEXT
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkAttachmentSampleLocationsEXT where
(VkAttachmentSampleLocationsEXT# Addr#
a ByteArray#
_) compare :: VkAttachmentSampleLocationsEXT
-> VkAttachmentSampleLocationsEXT -> Ordering
`compare`
x :: VkAttachmentSampleLocationsEXT
x@(VkAttachmentSampleLocationsEXT# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkAttachmentSampleLocationsEXT -> Int
forall a. Storable a => a -> Int
sizeOf VkAttachmentSampleLocationsEXT
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkAttachmentSampleLocationsEXT where
sizeOf :: VkAttachmentSampleLocationsEXT -> Int
sizeOf ~VkAttachmentSampleLocationsEXT
_ = (Int
48)
{-# LINE 567 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkAttachmentSampleLocationsEXT -> Int
alignment ~VkAttachmentSampleLocationsEXT
_
= Int
8
{-# LINE 571 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkAttachmentSampleLocationsEXT
-> IO VkAttachmentSampleLocationsEXT
peek = Ptr VkAttachmentSampleLocationsEXT
-> IO VkAttachmentSampleLocationsEXT
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkAttachmentSampleLocationsEXT
-> VkAttachmentSampleLocationsEXT -> IO ()
poke = Ptr VkAttachmentSampleLocationsEXT
-> VkAttachmentSampleLocationsEXT -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkAttachmentSampleLocationsEXT where
unsafeAddr :: VkAttachmentSampleLocationsEXT -> Addr#
unsafeAddr (VkAttachmentSampleLocationsEXT# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkAttachmentSampleLocationsEXT -> ByteArray#
unsafeByteArray (VkAttachmentSampleLocationsEXT# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkAttachmentSampleLocationsEXT
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkAttachmentSampleLocationsEXT
VkAttachmentSampleLocationsEXT#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkAttachmentSampleLocationsEXT where
type StructFields VkAttachmentSampleLocationsEXT =
'["attachmentIndex", "sampleLocationsInfo"]
type CUnionType VkAttachmentSampleLocationsEXT = 'False
type ReturnedOnly VkAttachmentSampleLocationsEXT = 'False
type StructExtends VkAttachmentSampleLocationsEXT = '[]
instance {-# OVERLAPPING #-}
HasField "attachmentIndex" VkAttachmentSampleLocationsEXT where
type FieldType "attachmentIndex" VkAttachmentSampleLocationsEXT =
Word32
type FieldOptional "attachmentIndex" VkAttachmentSampleLocationsEXT
= 'False
type FieldOffset "attachmentIndex" VkAttachmentSampleLocationsEXT =
(0)
{-# LINE 609 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "attachmentIndex" VkAttachmentSampleLocationsEXT
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 618 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "attachmentIndex" VkAttachmentSampleLocationsEXT where
{-# NOINLINE getField #-}
getField :: VkAttachmentSampleLocationsEXT
-> FieldType "attachmentIndex" VkAttachmentSampleLocationsEXT
getField VkAttachmentSampleLocationsEXT
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentSampleLocationsEXT -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentSampleLocationsEXT
-> Ptr VkAttachmentSampleLocationsEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentSampleLocationsEXT
x) (Int
0))
{-# LINE 625 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentSampleLocationsEXT
-> IO (FieldType "attachmentIndex" VkAttachmentSampleLocationsEXT)
readField Ptr VkAttachmentSampleLocationsEXT
p
= Ptr VkAttachmentSampleLocationsEXT -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentSampleLocationsEXT
p (Int
0)
{-# LINE 629 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "attachmentIndex" VkAttachmentSampleLocationsEXT
where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentSampleLocationsEXT
-> FieldType "attachmentIndex" VkAttachmentSampleLocationsEXT
-> IO ()
writeField Ptr VkAttachmentSampleLocationsEXT
p
= Ptr VkAttachmentSampleLocationsEXT -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentSampleLocationsEXT
p (Int
0)
{-# LINE 636 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "sampleLocationsInfo" VkAttachmentSampleLocationsEXT where
type FieldType "sampleLocationsInfo" VkAttachmentSampleLocationsEXT
= VkSampleLocationsInfoEXT
type FieldOptional "sampleLocationsInfo"
VkAttachmentSampleLocationsEXT
= 'False
type FieldOffset "sampleLocationsInfo"
VkAttachmentSampleLocationsEXT
=
(8)
{-# LINE 648 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
type FieldIsArray "sampleLocationsInfo"
VkAttachmentSampleLocationsEXT
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 658 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sampleLocationsInfo" VkAttachmentSampleLocationsEXT
where
{-# NOINLINE getField #-}
getField :: VkAttachmentSampleLocationsEXT
-> FieldType "sampleLocationsInfo" VkAttachmentSampleLocationsEXT
getField VkAttachmentSampleLocationsEXT
x
= IO VkSampleLocationsInfoEXT -> VkSampleLocationsInfoEXT
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkAttachmentSampleLocationsEXT
-> Int -> IO VkSampleLocationsInfoEXT
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkAttachmentSampleLocationsEXT
-> Ptr VkAttachmentSampleLocationsEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkAttachmentSampleLocationsEXT
x) (Int
8))
{-# LINE 666 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkAttachmentSampleLocationsEXT
-> IO
(FieldType "sampleLocationsInfo" VkAttachmentSampleLocationsEXT)
readField Ptr VkAttachmentSampleLocationsEXT
p
= Ptr VkAttachmentSampleLocationsEXT
-> Int -> IO VkSampleLocationsInfoEXT
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkAttachmentSampleLocationsEXT
p (Int
8)
{-# LINE 670 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sampleLocationsInfo" VkAttachmentSampleLocationsEXT
where
{-# INLINE writeField #-}
writeField :: Ptr VkAttachmentSampleLocationsEXT
-> FieldType "sampleLocationsInfo" VkAttachmentSampleLocationsEXT
-> IO ()
writeField Ptr VkAttachmentSampleLocationsEXT
p
= Ptr VkAttachmentSampleLocationsEXT
-> Int -> VkSampleLocationsInfoEXT -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkAttachmentSampleLocationsEXT
p (Int
8)
{-# LINE 677 "src-gen/Graphics/Vulkan/Types/Struct/Attachment.hsc" #-}
instance Show VkAttachmentSampleLocationsEXT where
showsPrec :: Int -> VkAttachmentSampleLocationsEXT -> ShowS
showsPrec Int
d VkAttachmentSampleLocationsEXT
x
= String -> ShowS
showString String
"VkAttachmentSampleLocationsEXT {" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
String -> ShowS
showString String
"attachmentIndex = " 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 (VkAttachmentSampleLocationsEXT
-> FieldType "attachmentIndex" VkAttachmentSampleLocationsEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"attachmentIndex" VkAttachmentSampleLocationsEXT
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
"sampleLocationsInfo = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkSampleLocationsInfoEXT -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkAttachmentSampleLocationsEXT
-> FieldType "sampleLocationsInfo" VkAttachmentSampleLocationsEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sampleLocationsInfo" VkAttachmentSampleLocationsEXT
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'