{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Vulkan.Types.Struct.InstanceCreateInfo
(VkInstanceCreateInfo(..)) 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.Bitmasks (VkInstanceCreateFlags)
import Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import Graphics.Vulkan.Types.Struct.ApplicationInfo (VkApplicationInfo)
import System.IO.Unsafe (unsafeDupablePerformIO)
data VkInstanceCreateInfo = VkInstanceCreateInfo# Addr# ByteArray#
instance Eq VkInstanceCreateInfo where
(VkInstanceCreateInfo# Addr#
a ByteArray#
_) == :: VkInstanceCreateInfo -> VkInstanceCreateInfo -> Bool
== x :: VkInstanceCreateInfo
x@(VkInstanceCreateInfo# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkInstanceCreateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkInstanceCreateInfo
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkInstanceCreateInfo where
(VkInstanceCreateInfo# Addr#
a ByteArray#
_) compare :: VkInstanceCreateInfo -> VkInstanceCreateInfo -> Ordering
`compare` x :: VkInstanceCreateInfo
x@(VkInstanceCreateInfo# Addr#
b ByteArray#
_)
= Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkInstanceCreateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkInstanceCreateInfo
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkInstanceCreateInfo where
sizeOf :: VkInstanceCreateInfo -> Int
sizeOf ~VkInstanceCreateInfo
_ = (Int
64)
{-# LINE 52 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkInstanceCreateInfo -> Int
alignment ~VkInstanceCreateInfo
_ = Int
8
{-# LINE 55 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkInstanceCreateInfo -> IO VkInstanceCreateInfo
peek = Ptr VkInstanceCreateInfo -> IO VkInstanceCreateInfo
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkInstanceCreateInfo -> VkInstanceCreateInfo -> IO ()
poke = Ptr VkInstanceCreateInfo -> VkInstanceCreateInfo -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkInstanceCreateInfo where
unsafeAddr :: VkInstanceCreateInfo -> Addr#
unsafeAddr (VkInstanceCreateInfo# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkInstanceCreateInfo -> ByteArray#
unsafeByteArray (VkInstanceCreateInfo# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkInstanceCreateInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkInstanceCreateInfo
VkInstanceCreateInfo# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkInstanceCreateInfo where
type StructFields VkInstanceCreateInfo =
'["sType", "pNext", "flags", "pApplicationInfo",
"enabledLayerCount", "ppEnabledLayerNames",
"enabledExtensionCount", "ppEnabledExtensionNames"]
type CUnionType VkInstanceCreateInfo = 'False
type ReturnedOnly VkInstanceCreateInfo = 'False
type StructExtends VkInstanceCreateInfo = '[]
instance {-# OVERLAPPING #-} HasField "sType" VkInstanceCreateInfo
where
type FieldType "sType" VkInstanceCreateInfo = VkStructureType
type FieldOptional "sType" VkInstanceCreateInfo = 'False
type FieldOffset "sType" VkInstanceCreateInfo =
(0)
{-# LINE 91 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
type FieldIsArray "sType" VkInstanceCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 98 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkInstanceCreateInfo where
{-# NOINLINE getField #-}
getField :: VkInstanceCreateInfo -> FieldType "sType" VkInstanceCreateInfo
getField VkInstanceCreateInfo
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkInstanceCreateInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInstanceCreateInfo -> Ptr VkInstanceCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInstanceCreateInfo
x) (Int
0))
{-# LINE 105 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkInstanceCreateInfo
-> IO (FieldType "sType" VkInstanceCreateInfo)
readField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInstanceCreateInfo
p (Int
0)
{-# LINE 109 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkInstanceCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkInstanceCreateInfo
-> FieldType "sType" VkInstanceCreateInfo -> IO ()
writeField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInstanceCreateInfo
p (Int
0)
{-# LINE 115 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-} HasField "pNext" VkInstanceCreateInfo
where
type FieldType "pNext" VkInstanceCreateInfo = Ptr Void
type FieldOptional "pNext" VkInstanceCreateInfo = 'False
type FieldOffset "pNext" VkInstanceCreateInfo =
(8)
{-# LINE 122 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
type FieldIsArray "pNext" VkInstanceCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 129 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkInstanceCreateInfo where
{-# NOINLINE getField #-}
getField :: VkInstanceCreateInfo -> FieldType "pNext" VkInstanceCreateInfo
getField VkInstanceCreateInfo
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkInstanceCreateInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInstanceCreateInfo -> Ptr VkInstanceCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInstanceCreateInfo
x) (Int
8))
{-# LINE 136 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkInstanceCreateInfo
-> IO (FieldType "pNext" VkInstanceCreateInfo)
readField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInstanceCreateInfo
p (Int
8)
{-# LINE 140 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkInstanceCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkInstanceCreateInfo
-> FieldType "pNext" VkInstanceCreateInfo -> IO ()
writeField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInstanceCreateInfo
p (Int
8)
{-# LINE 146 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-} HasField "flags" VkInstanceCreateInfo
where
type FieldType "flags" VkInstanceCreateInfo = VkInstanceCreateFlags
type FieldOptional "flags" VkInstanceCreateInfo = 'True
type FieldOffset "flags" VkInstanceCreateInfo =
(16)
{-# LINE 153 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
type FieldIsArray "flags" VkInstanceCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
16)
{-# LINE 160 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "flags" VkInstanceCreateInfo where
{-# NOINLINE getField #-}
getField :: VkInstanceCreateInfo -> FieldType "flags" VkInstanceCreateInfo
getField VkInstanceCreateInfo
x
= IO VkInstanceCreateFlags -> VkInstanceCreateFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkInstanceCreateInfo -> Int -> IO VkInstanceCreateFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInstanceCreateInfo -> Ptr VkInstanceCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInstanceCreateInfo
x) (Int
16))
{-# LINE 167 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkInstanceCreateInfo
-> IO (FieldType "flags" VkInstanceCreateInfo)
readField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> IO VkInstanceCreateFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInstanceCreateInfo
p (Int
16)
{-# LINE 171 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "flags" VkInstanceCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkInstanceCreateInfo
-> FieldType "flags" VkInstanceCreateInfo -> IO ()
writeField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> VkInstanceCreateFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInstanceCreateInfo
p (Int
16)
{-# LINE 177 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pApplicationInfo" VkInstanceCreateInfo where
type FieldType "pApplicationInfo" VkInstanceCreateInfo =
Ptr VkApplicationInfo
type FieldOptional "pApplicationInfo" VkInstanceCreateInfo = 'True
type FieldOffset "pApplicationInfo" VkInstanceCreateInfo =
(24)
{-# LINE 185 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
type FieldIsArray "pApplicationInfo" VkInstanceCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
24)
{-# LINE 193 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pApplicationInfo" VkInstanceCreateInfo where
{-# NOINLINE getField #-}
getField :: VkInstanceCreateInfo
-> FieldType "pApplicationInfo" VkInstanceCreateInfo
getField VkInstanceCreateInfo
x
= IO (Ptr VkApplicationInfo) -> Ptr VkApplicationInfo
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkInstanceCreateInfo -> Int -> IO (Ptr VkApplicationInfo)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInstanceCreateInfo -> Ptr VkInstanceCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInstanceCreateInfo
x) (Int
24))
{-# LINE 200 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkInstanceCreateInfo
-> IO (FieldType "pApplicationInfo" VkInstanceCreateInfo)
readField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> IO (Ptr VkApplicationInfo)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInstanceCreateInfo
p (Int
24)
{-# LINE 204 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pApplicationInfo" VkInstanceCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkInstanceCreateInfo
-> FieldType "pApplicationInfo" VkInstanceCreateInfo -> IO ()
writeField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> Ptr VkApplicationInfo -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInstanceCreateInfo
p (Int
24)
{-# LINE 210 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "enabledLayerCount" VkInstanceCreateInfo where
type FieldType "enabledLayerCount" VkInstanceCreateInfo = Word32
type FieldOptional "enabledLayerCount" VkInstanceCreateInfo = 'True
type FieldOffset "enabledLayerCount" VkInstanceCreateInfo =
(32)
{-# LINE 217 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
type FieldIsArray "enabledLayerCount" VkInstanceCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
32)
{-# LINE 225 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "enabledLayerCount" VkInstanceCreateInfo where
{-# NOINLINE getField #-}
getField :: VkInstanceCreateInfo
-> FieldType "enabledLayerCount" VkInstanceCreateInfo
getField VkInstanceCreateInfo
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkInstanceCreateInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInstanceCreateInfo -> Ptr VkInstanceCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInstanceCreateInfo
x) (Int
32))
{-# LINE 232 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkInstanceCreateInfo
-> IO (FieldType "enabledLayerCount" VkInstanceCreateInfo)
readField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInstanceCreateInfo
p (Int
32)
{-# LINE 236 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "enabledLayerCount" VkInstanceCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkInstanceCreateInfo
-> FieldType "enabledLayerCount" VkInstanceCreateInfo -> IO ()
writeField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInstanceCreateInfo
p (Int
32)
{-# LINE 242 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "ppEnabledLayerNames" VkInstanceCreateInfo where
type FieldType "ppEnabledLayerNames" VkInstanceCreateInfo =
Ptr CString
type FieldOptional "ppEnabledLayerNames" VkInstanceCreateInfo =
'False
type FieldOffset "ppEnabledLayerNames" VkInstanceCreateInfo =
(40)
{-# LINE 251 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
type FieldIsArray "ppEnabledLayerNames" VkInstanceCreateInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
40)
{-# LINE 260 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "ppEnabledLayerNames" VkInstanceCreateInfo where
{-# NOINLINE getField #-}
getField :: VkInstanceCreateInfo
-> FieldType "ppEnabledLayerNames" VkInstanceCreateInfo
getField VkInstanceCreateInfo
x
= IO (Ptr CString) -> Ptr CString
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkInstanceCreateInfo -> Int -> IO (Ptr CString)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInstanceCreateInfo -> Ptr VkInstanceCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInstanceCreateInfo
x) (Int
40))
{-# LINE 267 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkInstanceCreateInfo
-> IO (FieldType "ppEnabledLayerNames" VkInstanceCreateInfo)
readField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> IO (Ptr CString)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInstanceCreateInfo
p (Int
40)
{-# LINE 271 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "ppEnabledLayerNames" VkInstanceCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkInstanceCreateInfo
-> FieldType "ppEnabledLayerNames" VkInstanceCreateInfo -> IO ()
writeField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> Ptr CString -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInstanceCreateInfo
p (Int
40)
{-# LINE 277 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "enabledExtensionCount" VkInstanceCreateInfo where
type FieldType "enabledExtensionCount" VkInstanceCreateInfo =
Word32
type FieldOptional "enabledExtensionCount" VkInstanceCreateInfo =
'True
type FieldOffset "enabledExtensionCount" VkInstanceCreateInfo =
(48)
{-# LINE 286 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
type FieldIsArray "enabledExtensionCount" VkInstanceCreateInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
48)
{-# LINE 295 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "enabledExtensionCount" VkInstanceCreateInfo where
{-# NOINLINE getField #-}
getField :: VkInstanceCreateInfo
-> FieldType "enabledExtensionCount" VkInstanceCreateInfo
getField VkInstanceCreateInfo
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkInstanceCreateInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInstanceCreateInfo -> Ptr VkInstanceCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInstanceCreateInfo
x) (Int
48))
{-# LINE 302 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkInstanceCreateInfo
-> IO (FieldType "enabledExtensionCount" VkInstanceCreateInfo)
readField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInstanceCreateInfo
p (Int
48)
{-# LINE 306 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "enabledExtensionCount" VkInstanceCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkInstanceCreateInfo
-> FieldType "enabledExtensionCount" VkInstanceCreateInfo -> IO ()
writeField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInstanceCreateInfo
p (Int
48)
{-# LINE 312 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "ppEnabledExtensionNames" VkInstanceCreateInfo where
type FieldType "ppEnabledExtensionNames" VkInstanceCreateInfo =
Ptr CString
type FieldOptional "ppEnabledExtensionNames" VkInstanceCreateInfo =
'False
type FieldOffset "ppEnabledExtensionNames" VkInstanceCreateInfo =
(56)
{-# LINE 321 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
type FieldIsArray "ppEnabledExtensionNames" VkInstanceCreateInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
56)
{-# LINE 330 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "ppEnabledExtensionNames" VkInstanceCreateInfo where
{-# NOINLINE getField #-}
getField :: VkInstanceCreateInfo
-> FieldType "ppEnabledExtensionNames" VkInstanceCreateInfo
getField VkInstanceCreateInfo
x
= IO (Ptr CString) -> Ptr CString
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkInstanceCreateInfo -> Int -> IO (Ptr CString)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkInstanceCreateInfo -> Ptr VkInstanceCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkInstanceCreateInfo
x) (Int
56))
{-# LINE 337 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkInstanceCreateInfo
-> IO (FieldType "ppEnabledExtensionNames" VkInstanceCreateInfo)
readField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> IO (Ptr CString)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkInstanceCreateInfo
p (Int
56)
{-# LINE 341 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "ppEnabledExtensionNames" VkInstanceCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkInstanceCreateInfo
-> FieldType "ppEnabledExtensionNames" VkInstanceCreateInfo
-> IO ()
writeField Ptr VkInstanceCreateInfo
p
= Ptr VkInstanceCreateInfo -> Int -> Ptr CString -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkInstanceCreateInfo
p (Int
56)
{-# LINE 347 "src-gen/Graphics/Vulkan/Types/Struct/InstanceCreateInfo.hsc" #-}
instance Show VkInstanceCreateInfo where
showsPrec :: Int -> VkInstanceCreateInfo -> ShowS
showsPrec Int
d VkInstanceCreateInfo
x
= String -> ShowS
showString String
"VkInstanceCreateInfo {" 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 (VkInstanceCreateInfo -> FieldType "sType" VkInstanceCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkInstanceCreateInfo
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 (VkInstanceCreateInfo -> FieldType "pNext" VkInstanceCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkInstanceCreateInfo
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 -> VkInstanceCreateFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkInstanceCreateInfo -> FieldType "flags" VkInstanceCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkInstanceCreateInfo
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
"pApplicationInfo = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> Ptr VkApplicationInfo -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkInstanceCreateInfo
-> FieldType "pApplicationInfo" VkInstanceCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pApplicationInfo" VkInstanceCreateInfo
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
"enabledLayerCount = " 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 (VkInstanceCreateInfo
-> FieldType "enabledLayerCount" VkInstanceCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"enabledLayerCount" VkInstanceCreateInfo
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
"ppEnabledLayerNames = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> Ptr CString -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkInstanceCreateInfo
-> FieldType "ppEnabledLayerNames" VkInstanceCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"ppEnabledLayerNames" VkInstanceCreateInfo
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
"enabledExtensionCount = " 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
(VkInstanceCreateInfo
-> FieldType "enabledExtensionCount" VkInstanceCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"enabledExtensionCount" VkInstanceCreateInfo
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
"ppEnabledExtensionNames = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> Ptr CString -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d
(VkInstanceCreateInfo
-> FieldType "ppEnabledExtensionNames" VkInstanceCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"ppEnabledExtensionNames" VkInstanceCreateInfo
x)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'