{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Vulkan.Types.Struct.MultisamplePropertiesEXT
(VkMultisamplePropertiesEXT(..)) 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.StructureType (VkStructureType)
import Graphics.Vulkan.Types.Struct.Extent (VkExtent2D)
import System.IO.Unsafe (unsafeDupablePerformIO)
data VkMultisamplePropertiesEXT = VkMultisamplePropertiesEXT# Addr#
ByteArray#
instance Eq VkMultisamplePropertiesEXT where
(VkMultisamplePropertiesEXT# Addr#
a ByteArray#
_) == :: VkMultisamplePropertiesEXT -> VkMultisamplePropertiesEXT -> Bool
==
x :: VkMultisamplePropertiesEXT
x@(VkMultisamplePropertiesEXT# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkMultisamplePropertiesEXT -> Int
forall a. Storable a => a -> Int
sizeOf VkMultisamplePropertiesEXT
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkMultisamplePropertiesEXT where
(VkMultisamplePropertiesEXT# Addr#
a ByteArray#
_) compare :: VkMultisamplePropertiesEXT
-> VkMultisamplePropertiesEXT -> Ordering
`compare`
x :: VkMultisamplePropertiesEXT
x@(VkMultisamplePropertiesEXT# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkMultisamplePropertiesEXT -> Int
forall a. Storable a => a -> Int
sizeOf VkMultisamplePropertiesEXT
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkMultisamplePropertiesEXT where
sizeOf :: VkMultisamplePropertiesEXT -> Int
sizeOf ~VkMultisamplePropertiesEXT
_ = (Int
24)
{-# LINE 47 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkMultisamplePropertiesEXT -> Int
alignment ~VkMultisamplePropertiesEXT
_ = Int
8
{-# LINE 50 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkMultisamplePropertiesEXT -> IO VkMultisamplePropertiesEXT
peek = Ptr VkMultisamplePropertiesEXT -> IO VkMultisamplePropertiesEXT
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkMultisamplePropertiesEXT
-> VkMultisamplePropertiesEXT -> IO ()
poke = Ptr VkMultisamplePropertiesEXT
-> VkMultisamplePropertiesEXT -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkMultisamplePropertiesEXT where
unsafeAddr :: VkMultisamplePropertiesEXT -> Addr#
unsafeAddr (VkMultisamplePropertiesEXT# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkMultisamplePropertiesEXT -> ByteArray#
unsafeByteArray (VkMultisamplePropertiesEXT# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkMultisamplePropertiesEXT
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkMultisamplePropertiesEXT
VkMultisamplePropertiesEXT#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkMultisamplePropertiesEXT where
type StructFields VkMultisamplePropertiesEXT =
'["sType", "pNext", "maxSampleLocationGridSize"]
type CUnionType VkMultisamplePropertiesEXT = 'False
type ReturnedOnly VkMultisamplePropertiesEXT = 'True
type StructExtends VkMultisamplePropertiesEXT = '[]
instance {-# OVERLAPPING #-}
HasField "sType" VkMultisamplePropertiesEXT where
type FieldType "sType" VkMultisamplePropertiesEXT = VkStructureType
type FieldOptional "sType" VkMultisamplePropertiesEXT = 'False
type FieldOffset "sType" VkMultisamplePropertiesEXT =
(0)
{-# LINE 86 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
type FieldIsArray "sType" VkMultisamplePropertiesEXT = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 94 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkMultisamplePropertiesEXT where
{-# NOINLINE getField #-}
getField :: VkMultisamplePropertiesEXT
-> FieldType "sType" VkMultisamplePropertiesEXT
getField VkMultisamplePropertiesEXT
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkMultisamplePropertiesEXT -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkMultisamplePropertiesEXT -> Ptr VkMultisamplePropertiesEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkMultisamplePropertiesEXT
x) (Int
0))
{-# LINE 101 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkMultisamplePropertiesEXT
-> IO (FieldType "sType" VkMultisamplePropertiesEXT)
readField Ptr VkMultisamplePropertiesEXT
p
= Ptr VkMultisamplePropertiesEXT -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMultisamplePropertiesEXT
p (Int
0)
{-# LINE 105 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkMultisamplePropertiesEXT where
{-# INLINE writeField #-}
writeField :: Ptr VkMultisamplePropertiesEXT
-> FieldType "sType" VkMultisamplePropertiesEXT -> IO ()
writeField Ptr VkMultisamplePropertiesEXT
p
= Ptr VkMultisamplePropertiesEXT -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMultisamplePropertiesEXT
p (Int
0)
{-# LINE 111 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkMultisamplePropertiesEXT where
type FieldType "pNext" VkMultisamplePropertiesEXT = Ptr Void
type FieldOptional "pNext" VkMultisamplePropertiesEXT = 'False
type FieldOffset "pNext" VkMultisamplePropertiesEXT =
(8)
{-# LINE 118 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
type FieldIsArray "pNext" VkMultisamplePropertiesEXT = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 126 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkMultisamplePropertiesEXT where
{-# NOINLINE getField #-}
getField :: VkMultisamplePropertiesEXT
-> FieldType "pNext" VkMultisamplePropertiesEXT
getField VkMultisamplePropertiesEXT
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkMultisamplePropertiesEXT -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkMultisamplePropertiesEXT -> Ptr VkMultisamplePropertiesEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkMultisamplePropertiesEXT
x) (Int
8))
{-# LINE 133 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkMultisamplePropertiesEXT
-> IO (FieldType "pNext" VkMultisamplePropertiesEXT)
readField Ptr VkMultisamplePropertiesEXT
p
= Ptr VkMultisamplePropertiesEXT -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMultisamplePropertiesEXT
p (Int
8)
{-# LINE 137 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkMultisamplePropertiesEXT where
{-# INLINE writeField #-}
writeField :: Ptr VkMultisamplePropertiesEXT
-> FieldType "pNext" VkMultisamplePropertiesEXT -> IO ()
writeField Ptr VkMultisamplePropertiesEXT
p
= Ptr VkMultisamplePropertiesEXT -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMultisamplePropertiesEXT
p (Int
8)
{-# LINE 143 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "maxSampleLocationGridSize" VkMultisamplePropertiesEXT
where
type FieldType "maxSampleLocationGridSize"
VkMultisamplePropertiesEXT
= VkExtent2D
type FieldOptional "maxSampleLocationGridSize"
VkMultisamplePropertiesEXT
= 'False
type FieldOffset "maxSampleLocationGridSize"
VkMultisamplePropertiesEXT
=
(16)
{-# LINE 157 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
type FieldIsArray "maxSampleLocationGridSize"
VkMultisamplePropertiesEXT
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 167 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "maxSampleLocationGridSize" VkMultisamplePropertiesEXT
where
{-# NOINLINE getField #-}
getField :: VkMultisamplePropertiesEXT
-> FieldType "maxSampleLocationGridSize" VkMultisamplePropertiesEXT
getField VkMultisamplePropertiesEXT
x
= IO VkExtent2D -> VkExtent2D
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkMultisamplePropertiesEXT -> Int -> IO VkExtent2D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkMultisamplePropertiesEXT -> Ptr VkMultisamplePropertiesEXT
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkMultisamplePropertiesEXT
x) (Int
16))
{-# LINE 175 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkMultisamplePropertiesEXT
-> IO
(FieldType "maxSampleLocationGridSize" VkMultisamplePropertiesEXT)
readField Ptr VkMultisamplePropertiesEXT
p
= Ptr VkMultisamplePropertiesEXT -> Int -> IO VkExtent2D
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkMultisamplePropertiesEXT
p (Int
16)
{-# LINE 179 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "maxSampleLocationGridSize"
VkMultisamplePropertiesEXT
where
{-# INLINE writeField #-}
writeField :: Ptr VkMultisamplePropertiesEXT
-> FieldType "maxSampleLocationGridSize" VkMultisamplePropertiesEXT
-> IO ()
writeField Ptr VkMultisamplePropertiesEXT
p
= Ptr VkMultisamplePropertiesEXT -> Int -> VkExtent2D -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkMultisamplePropertiesEXT
p (Int
16)
{-# LINE 187 "src-gen/Graphics/Vulkan/Types/Struct/MultisamplePropertiesEXT.hsc" #-}
instance Show VkMultisamplePropertiesEXT where
showsPrec :: Int -> VkMultisamplePropertiesEXT -> ShowS
showsPrec Int
d VkMultisamplePropertiesEXT
x
= String -> ShowS
showString String
"VkMultisamplePropertiesEXT {" 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 (VkMultisamplePropertiesEXT
-> FieldType "sType" VkMultisamplePropertiesEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkMultisamplePropertiesEXT
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 (VkMultisamplePropertiesEXT
-> FieldType "pNext" VkMultisamplePropertiesEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkMultisamplePropertiesEXT
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
"maxSampleLocationGridSize = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkExtent2D -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkMultisamplePropertiesEXT
-> FieldType "maxSampleLocationGridSize" VkMultisamplePropertiesEXT
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"maxSampleLocationGridSize" VkMultisamplePropertiesEXT
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Char -> ShowS
showChar Char
'}'