{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Vulkan.Types.Struct.Command
(VkCommandBufferAllocateInfo(..), VkCommandBufferBeginInfo(..),
VkCommandBufferInheritanceInfo(..), VkCommandPoolCreateInfo(..))
where
import Foreign.Storable (Storable (..))
import GHC.Base (Addr#, ByteArray#,
byteArrayContents#,
plusAddr#)
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Internal
import Graphics.Vulkan.Types.BaseTypes (VkBool32)
import Graphics.Vulkan.Types.Enum.Command (VkCommandBufferLevel, VkCommandBufferUsageFlags,
VkCommandPoolCreateFlags)
import Graphics.Vulkan.Types.Enum.Query (VkQueryControlFlags, VkQueryPipelineStatisticFlags)
import Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import Graphics.Vulkan.Types.Handles (VkCommandPool,
VkFramebuffer,
VkRenderPass)
import System.IO.Unsafe (unsafeDupablePerformIO)
data VkCommandBufferAllocateInfo = VkCommandBufferAllocateInfo# Addr#
ByteArray#
instance Eq VkCommandBufferAllocateInfo where
(VkCommandBufferAllocateInfo# Addr#
a ByteArray#
_) == :: VkCommandBufferAllocateInfo -> VkCommandBufferAllocateInfo -> Bool
==
x :: VkCommandBufferAllocateInfo
x@(VkCommandBufferAllocateInfo# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCommandBufferAllocateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkCommandBufferAllocateInfo
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkCommandBufferAllocateInfo where
(VkCommandBufferAllocateInfo# Addr#
a ByteArray#
_) compare :: VkCommandBufferAllocateInfo
-> VkCommandBufferAllocateInfo -> Ordering
`compare`
x :: VkCommandBufferAllocateInfo
x@(VkCommandBufferAllocateInfo# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCommandBufferAllocateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkCommandBufferAllocateInfo
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkCommandBufferAllocateInfo where
sizeOf :: VkCommandBufferAllocateInfo -> Int
sizeOf ~VkCommandBufferAllocateInfo
_ = (Int
32)
{-# LINE 57 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkCommandBufferAllocateInfo -> Int
alignment ~VkCommandBufferAllocateInfo
_ = Int
8
{-# LINE 60 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkCommandBufferAllocateInfo -> IO VkCommandBufferAllocateInfo
peek = Ptr VkCommandBufferAllocateInfo -> IO VkCommandBufferAllocateInfo
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkCommandBufferAllocateInfo
-> VkCommandBufferAllocateInfo -> IO ()
poke = Ptr VkCommandBufferAllocateInfo
-> VkCommandBufferAllocateInfo -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkCommandBufferAllocateInfo where
unsafeAddr :: VkCommandBufferAllocateInfo -> Addr#
unsafeAddr (VkCommandBufferAllocateInfo# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkCommandBufferAllocateInfo -> ByteArray#
unsafeByteArray (VkCommandBufferAllocateInfo# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkCommandBufferAllocateInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkCommandBufferAllocateInfo
VkCommandBufferAllocateInfo#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkCommandBufferAllocateInfo where
type StructFields VkCommandBufferAllocateInfo =
'["sType", "pNext", "commandPool", "level", "commandBufferCount"]
type CUnionType VkCommandBufferAllocateInfo = 'False
type ReturnedOnly VkCommandBufferAllocateInfo = 'False
type StructExtends VkCommandBufferAllocateInfo = '[]
instance {-# OVERLAPPING #-}
HasField "sType" VkCommandBufferAllocateInfo where
type FieldType "sType" VkCommandBufferAllocateInfo =
VkStructureType
type FieldOptional "sType" VkCommandBufferAllocateInfo = 'False
type FieldOffset "sType" VkCommandBufferAllocateInfo =
(0)
{-# LINE 97 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "sType" VkCommandBufferAllocateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 105 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkCommandBufferAllocateInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferAllocateInfo
-> FieldType "sType" VkCommandBufferAllocateInfo
getField VkCommandBufferAllocateInfo
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferAllocateInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferAllocateInfo -> Ptr VkCommandBufferAllocateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferAllocateInfo
x) (Int
0))
{-# LINE 112 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferAllocateInfo
-> IO (FieldType "sType" VkCommandBufferAllocateInfo)
readField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferAllocateInfo
p (Int
0)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkCommandBufferAllocateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferAllocateInfo
-> FieldType "sType" VkCommandBufferAllocateInfo -> IO ()
writeField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferAllocateInfo
p (Int
0)
{-# LINE 122 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkCommandBufferAllocateInfo where
type FieldType "pNext" VkCommandBufferAllocateInfo = Ptr Void
type FieldOptional "pNext" VkCommandBufferAllocateInfo = 'False
type FieldOffset "pNext" VkCommandBufferAllocateInfo =
(8)
{-# LINE 129 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "pNext" VkCommandBufferAllocateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 137 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkCommandBufferAllocateInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferAllocateInfo
-> FieldType "pNext" VkCommandBufferAllocateInfo
getField VkCommandBufferAllocateInfo
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferAllocateInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferAllocateInfo -> Ptr VkCommandBufferAllocateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferAllocateInfo
x) (Int
8))
{-# LINE 144 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferAllocateInfo
-> IO (FieldType "pNext" VkCommandBufferAllocateInfo)
readField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferAllocateInfo
p (Int
8)
{-# LINE 148 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkCommandBufferAllocateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferAllocateInfo
-> FieldType "pNext" VkCommandBufferAllocateInfo -> IO ()
writeField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferAllocateInfo
p (Int
8)
{-# LINE 154 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "commandPool" VkCommandBufferAllocateInfo where
type FieldType "commandPool" VkCommandBufferAllocateInfo =
VkCommandPool
type FieldOptional "commandPool" VkCommandBufferAllocateInfo =
'False
type FieldOffset "commandPool" VkCommandBufferAllocateInfo =
(16)
{-# LINE 163 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "commandPool" VkCommandBufferAllocateInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 172 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "commandPool" VkCommandBufferAllocateInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferAllocateInfo
-> FieldType "commandPool" VkCommandBufferAllocateInfo
getField VkCommandBufferAllocateInfo
x
= IO VkCommandPool -> VkCommandPool
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferAllocateInfo -> Int -> IO VkCommandPool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferAllocateInfo -> Ptr VkCommandBufferAllocateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferAllocateInfo
x) (Int
16))
{-# LINE 179 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferAllocateInfo
-> IO (FieldType "commandPool" VkCommandBufferAllocateInfo)
readField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo -> Int -> IO VkCommandPool
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferAllocateInfo
p (Int
16)
{-# LINE 183 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "commandPool" VkCommandBufferAllocateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferAllocateInfo
-> FieldType "commandPool" VkCommandBufferAllocateInfo -> IO ()
writeField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo -> Int -> VkCommandPool -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferAllocateInfo
p (Int
16)
{-# LINE 189 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "level" VkCommandBufferAllocateInfo where
type FieldType "level" VkCommandBufferAllocateInfo =
VkCommandBufferLevel
type FieldOptional "level" VkCommandBufferAllocateInfo = 'False
type FieldOffset "level" VkCommandBufferAllocateInfo =
(24)
{-# LINE 197 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "level" VkCommandBufferAllocateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
24)
{-# LINE 205 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "level" VkCommandBufferAllocateInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferAllocateInfo
-> FieldType "level" VkCommandBufferAllocateInfo
getField VkCommandBufferAllocateInfo
x
= IO VkCommandBufferLevel -> VkCommandBufferLevel
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferAllocateInfo -> Int -> IO VkCommandBufferLevel
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferAllocateInfo -> Ptr VkCommandBufferAllocateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferAllocateInfo
x) (Int
24))
{-# LINE 212 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferAllocateInfo
-> IO (FieldType "level" VkCommandBufferAllocateInfo)
readField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo -> Int -> IO VkCommandBufferLevel
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferAllocateInfo
p (Int
24)
{-# LINE 216 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "level" VkCommandBufferAllocateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferAllocateInfo
-> FieldType "level" VkCommandBufferAllocateInfo -> IO ()
writeField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo
-> Int -> VkCommandBufferLevel -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferAllocateInfo
p (Int
24)
{-# LINE 222 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "commandBufferCount" VkCommandBufferAllocateInfo where
type FieldType "commandBufferCount" VkCommandBufferAllocateInfo =
Word32
type FieldOptional "commandBufferCount" VkCommandBufferAllocateInfo
= 'False
type FieldOffset "commandBufferCount" VkCommandBufferAllocateInfo =
(28)
{-# LINE 231 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "commandBufferCount" VkCommandBufferAllocateInfo
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
28)
{-# LINE 240 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "commandBufferCount" VkCommandBufferAllocateInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferAllocateInfo
-> FieldType "commandBufferCount" VkCommandBufferAllocateInfo
getField VkCommandBufferAllocateInfo
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferAllocateInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferAllocateInfo -> Ptr VkCommandBufferAllocateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferAllocateInfo
x) (Int
28))
{-# LINE 247 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferAllocateInfo
-> IO (FieldType "commandBufferCount" VkCommandBufferAllocateInfo)
readField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferAllocateInfo
p (Int
28)
{-# LINE 251 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "commandBufferCount" VkCommandBufferAllocateInfo
where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferAllocateInfo
-> FieldType "commandBufferCount" VkCommandBufferAllocateInfo
-> IO ()
writeField Ptr VkCommandBufferAllocateInfo
p
= Ptr VkCommandBufferAllocateInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferAllocateInfo
p (Int
28)
{-# LINE 258 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance Show VkCommandBufferAllocateInfo where
showsPrec :: Int -> VkCommandBufferAllocateInfo -> ShowS
showsPrec Int
d VkCommandBufferAllocateInfo
x
= String -> ShowS
showString String
"VkCommandBufferAllocateInfo {" 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 (VkCommandBufferAllocateInfo
-> FieldType "sType" VkCommandBufferAllocateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkCommandBufferAllocateInfo
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 (VkCommandBufferAllocateInfo
-> FieldType "pNext" VkCommandBufferAllocateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkCommandBufferAllocateInfo
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
"commandPool = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkCommandPool -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCommandBufferAllocateInfo
-> FieldType "commandPool" VkCommandBufferAllocateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"commandPool" VkCommandBufferAllocateInfo
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
"level = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkCommandBufferLevel -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCommandBufferAllocateInfo
-> FieldType "level" VkCommandBufferAllocateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"level" VkCommandBufferAllocateInfo
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
"commandBufferCount = " 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 (VkCommandBufferAllocateInfo
-> FieldType "commandBufferCount" VkCommandBufferAllocateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"commandBufferCount" VkCommandBufferAllocateInfo
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Char -> ShowS
showChar Char
'}'
data VkCommandBufferBeginInfo = VkCommandBufferBeginInfo# Addr#
ByteArray#
instance Eq VkCommandBufferBeginInfo where
(VkCommandBufferBeginInfo# Addr#
a ByteArray#
_) == :: VkCommandBufferBeginInfo -> VkCommandBufferBeginInfo -> Bool
==
x :: VkCommandBufferBeginInfo
x@(VkCommandBufferBeginInfo# Addr#
b ByteArray#
_) = Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCommandBufferBeginInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkCommandBufferBeginInfo
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkCommandBufferBeginInfo where
(VkCommandBufferBeginInfo# Addr#
a ByteArray#
_) compare :: VkCommandBufferBeginInfo -> VkCommandBufferBeginInfo -> Ordering
`compare`
x :: VkCommandBufferBeginInfo
x@(VkCommandBufferBeginInfo# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCommandBufferBeginInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkCommandBufferBeginInfo
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkCommandBufferBeginInfo where
sizeOf :: VkCommandBufferBeginInfo -> Int
sizeOf ~VkCommandBufferBeginInfo
_ = (Int
32)
{-# LINE 303 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkCommandBufferBeginInfo -> Int
alignment ~VkCommandBufferBeginInfo
_ = Int
8
{-# LINE 306 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkCommandBufferBeginInfo -> IO VkCommandBufferBeginInfo
peek = Ptr VkCommandBufferBeginInfo -> IO VkCommandBufferBeginInfo
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkCommandBufferBeginInfo -> VkCommandBufferBeginInfo -> IO ()
poke = Ptr VkCommandBufferBeginInfo -> VkCommandBufferBeginInfo -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkCommandBufferBeginInfo where
unsafeAddr :: VkCommandBufferBeginInfo -> Addr#
unsafeAddr (VkCommandBufferBeginInfo# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkCommandBufferBeginInfo -> ByteArray#
unsafeByteArray (VkCommandBufferBeginInfo# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkCommandBufferBeginInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkCommandBufferBeginInfo
VkCommandBufferBeginInfo# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkCommandBufferBeginInfo where
type StructFields VkCommandBufferBeginInfo =
'["sType", "pNext", "flags", "pInheritanceInfo"]
type CUnionType VkCommandBufferBeginInfo = 'False
type ReturnedOnly VkCommandBufferBeginInfo = 'False
type StructExtends VkCommandBufferBeginInfo = '[]
instance {-# OVERLAPPING #-}
HasField "sType" VkCommandBufferBeginInfo where
type FieldType "sType" VkCommandBufferBeginInfo = VkStructureType
type FieldOptional "sType" VkCommandBufferBeginInfo = 'False
type FieldOffset "sType" VkCommandBufferBeginInfo =
(0)
{-# LINE 341 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "sType" VkCommandBufferBeginInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 348 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkCommandBufferBeginInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferBeginInfo
-> FieldType "sType" VkCommandBufferBeginInfo
getField VkCommandBufferBeginInfo
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferBeginInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferBeginInfo -> Ptr VkCommandBufferBeginInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferBeginInfo
x) (Int
0))
{-# LINE 355 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferBeginInfo
-> IO (FieldType "sType" VkCommandBufferBeginInfo)
readField Ptr VkCommandBufferBeginInfo
p
= Ptr VkCommandBufferBeginInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferBeginInfo
p (Int
0)
{-# LINE 359 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkCommandBufferBeginInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferBeginInfo
-> FieldType "sType" VkCommandBufferBeginInfo -> IO ()
writeField Ptr VkCommandBufferBeginInfo
p
= Ptr VkCommandBufferBeginInfo -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferBeginInfo
p (Int
0)
{-# LINE 365 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkCommandBufferBeginInfo where
type FieldType "pNext" VkCommandBufferBeginInfo = Ptr Void
type FieldOptional "pNext" VkCommandBufferBeginInfo = 'False
type FieldOffset "pNext" VkCommandBufferBeginInfo =
(8)
{-# LINE 372 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "pNext" VkCommandBufferBeginInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 379 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkCommandBufferBeginInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferBeginInfo
-> FieldType "pNext" VkCommandBufferBeginInfo
getField VkCommandBufferBeginInfo
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferBeginInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferBeginInfo -> Ptr VkCommandBufferBeginInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferBeginInfo
x) (Int
8))
{-# LINE 386 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferBeginInfo
-> IO (FieldType "pNext" VkCommandBufferBeginInfo)
readField Ptr VkCommandBufferBeginInfo
p
= Ptr VkCommandBufferBeginInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferBeginInfo
p (Int
8)
{-# LINE 390 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkCommandBufferBeginInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferBeginInfo
-> FieldType "pNext" VkCommandBufferBeginInfo -> IO ()
writeField Ptr VkCommandBufferBeginInfo
p
= Ptr VkCommandBufferBeginInfo -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferBeginInfo
p (Int
8)
{-# LINE 396 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "flags" VkCommandBufferBeginInfo where
type FieldType "flags" VkCommandBufferBeginInfo =
VkCommandBufferUsageFlags
type FieldOptional "flags" VkCommandBufferBeginInfo = 'True
type FieldOffset "flags" VkCommandBufferBeginInfo =
(16)
{-# LINE 404 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "flags" VkCommandBufferBeginInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
16)
{-# LINE 411 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "flags" VkCommandBufferBeginInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferBeginInfo
-> FieldType "flags" VkCommandBufferBeginInfo
getField VkCommandBufferBeginInfo
x
= IO VkCommandBufferUsageFlags -> VkCommandBufferUsageFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferBeginInfo -> Int -> IO VkCommandBufferUsageFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferBeginInfo -> Ptr VkCommandBufferBeginInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferBeginInfo
x) (Int
16))
{-# LINE 418 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferBeginInfo
-> IO (FieldType "flags" VkCommandBufferBeginInfo)
readField Ptr VkCommandBufferBeginInfo
p
= Ptr VkCommandBufferBeginInfo -> Int -> IO VkCommandBufferUsageFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferBeginInfo
p (Int
16)
{-# LINE 422 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "flags" VkCommandBufferBeginInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferBeginInfo
-> FieldType "flags" VkCommandBufferBeginInfo -> IO ()
writeField Ptr VkCommandBufferBeginInfo
p
= Ptr VkCommandBufferBeginInfo
-> Int -> VkCommandBufferUsageFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferBeginInfo
p (Int
16)
{-# LINE 428 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pInheritanceInfo" VkCommandBufferBeginInfo where
type FieldType "pInheritanceInfo" VkCommandBufferBeginInfo =
Ptr VkCommandBufferInheritanceInfo
type FieldOptional "pInheritanceInfo" VkCommandBufferBeginInfo =
'True
type FieldOffset "pInheritanceInfo" VkCommandBufferBeginInfo =
(24)
{-# LINE 437 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "pInheritanceInfo" VkCommandBufferBeginInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
24)
{-# LINE 446 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pInheritanceInfo" VkCommandBufferBeginInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferBeginInfo
-> FieldType "pInheritanceInfo" VkCommandBufferBeginInfo
getField VkCommandBufferBeginInfo
x
= IO (Ptr VkCommandBufferInheritanceInfo)
-> Ptr VkCommandBufferInheritanceInfo
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferBeginInfo
-> Int -> IO (Ptr VkCommandBufferInheritanceInfo)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferBeginInfo -> Ptr VkCommandBufferBeginInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferBeginInfo
x) (Int
24))
{-# LINE 453 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferBeginInfo
-> IO (FieldType "pInheritanceInfo" VkCommandBufferBeginInfo)
readField Ptr VkCommandBufferBeginInfo
p
= Ptr VkCommandBufferBeginInfo
-> Int -> IO (Ptr VkCommandBufferInheritanceInfo)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferBeginInfo
p (Int
24)
{-# LINE 457 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pInheritanceInfo" VkCommandBufferBeginInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferBeginInfo
-> FieldType "pInheritanceInfo" VkCommandBufferBeginInfo -> IO ()
writeField Ptr VkCommandBufferBeginInfo
p
= Ptr VkCommandBufferBeginInfo
-> Int -> Ptr VkCommandBufferInheritanceInfo -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferBeginInfo
p (Int
24)
{-# LINE 463 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance Show VkCommandBufferBeginInfo where
showsPrec :: Int -> VkCommandBufferBeginInfo -> ShowS
showsPrec Int
d VkCommandBufferBeginInfo
x
= String -> ShowS
showString String
"VkCommandBufferBeginInfo {" 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 (VkCommandBufferBeginInfo
-> FieldType "sType" VkCommandBufferBeginInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkCommandBufferBeginInfo
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 (VkCommandBufferBeginInfo
-> FieldType "pNext" VkCommandBufferBeginInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkCommandBufferBeginInfo
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 -> VkCommandBufferUsageFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCommandBufferBeginInfo
-> FieldType "flags" VkCommandBufferBeginInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkCommandBufferBeginInfo
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
"pInheritanceInfo = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> Ptr VkCommandBufferInheritanceInfo -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCommandBufferBeginInfo
-> FieldType "pInheritanceInfo" VkCommandBufferBeginInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pInheritanceInfo" VkCommandBufferBeginInfo
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkCommandBufferInheritanceInfo = VkCommandBufferInheritanceInfo# Addr#
ByteArray#
instance Eq VkCommandBufferInheritanceInfo where
(VkCommandBufferInheritanceInfo# Addr#
a ByteArray#
_) == :: VkCommandBufferInheritanceInfo
-> VkCommandBufferInheritanceInfo -> Bool
==
x :: VkCommandBufferInheritanceInfo
x@(VkCommandBufferInheritanceInfo# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCommandBufferInheritanceInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkCommandBufferInheritanceInfo
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkCommandBufferInheritanceInfo where
(VkCommandBufferInheritanceInfo# Addr#
a ByteArray#
_) compare :: VkCommandBufferInheritanceInfo
-> VkCommandBufferInheritanceInfo -> Ordering
`compare`
x :: VkCommandBufferInheritanceInfo
x@(VkCommandBufferInheritanceInfo# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCommandBufferInheritanceInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkCommandBufferInheritanceInfo
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkCommandBufferInheritanceInfo where
sizeOf :: VkCommandBufferInheritanceInfo -> Int
sizeOf ~VkCommandBufferInheritanceInfo
_ = (Int
56)
{-# LINE 509 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkCommandBufferInheritanceInfo -> Int
alignment ~VkCommandBufferInheritanceInfo
_
= Int
8
{-# LINE 513 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkCommandBufferInheritanceInfo
-> IO VkCommandBufferInheritanceInfo
peek = Ptr VkCommandBufferInheritanceInfo
-> IO VkCommandBufferInheritanceInfo
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkCommandBufferInheritanceInfo
-> VkCommandBufferInheritanceInfo -> IO ()
poke = Ptr VkCommandBufferInheritanceInfo
-> VkCommandBufferInheritanceInfo -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkCommandBufferInheritanceInfo where
unsafeAddr :: VkCommandBufferInheritanceInfo -> Addr#
unsafeAddr (VkCommandBufferInheritanceInfo# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkCommandBufferInheritanceInfo -> ByteArray#
unsafeByteArray (VkCommandBufferInheritanceInfo# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkCommandBufferInheritanceInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkCommandBufferInheritanceInfo
VkCommandBufferInheritanceInfo#
(Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off)
ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkCommandBufferInheritanceInfo where
type StructFields VkCommandBufferInheritanceInfo =
'["sType", "pNext", "renderPass", "subpass", "framebuffer",
"occlusionQueryEnable", "queryFlags", "pipelineStatistics"]
type CUnionType VkCommandBufferInheritanceInfo = 'False
type ReturnedOnly VkCommandBufferInheritanceInfo = 'False
type StructExtends VkCommandBufferInheritanceInfo = '[]
instance {-# OVERLAPPING #-}
HasField "sType" VkCommandBufferInheritanceInfo where
type FieldType "sType" VkCommandBufferInheritanceInfo =
VkStructureType
type FieldOptional "sType" VkCommandBufferInheritanceInfo = 'False
type FieldOffset "sType" VkCommandBufferInheritanceInfo =
(0)
{-# LINE 551 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "sType" VkCommandBufferInheritanceInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
0)
{-# LINE 559 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkCommandBufferInheritanceInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferInheritanceInfo
-> FieldType "sType" VkCommandBufferInheritanceInfo
getField VkCommandBufferInheritanceInfo
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferInheritanceInfo
-> Ptr VkCommandBufferInheritanceInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferInheritanceInfo
x) (Int
0))
{-# LINE 566 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferInheritanceInfo
-> IO (FieldType "sType" VkCommandBufferInheritanceInfo)
readField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
0)
{-# LINE 570 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkCommandBufferInheritanceInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferInheritanceInfo
-> FieldType "sType" VkCommandBufferInheritanceInfo -> IO ()
writeField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo
-> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
0)
{-# LINE 576 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkCommandBufferInheritanceInfo where
type FieldType "pNext" VkCommandBufferInheritanceInfo = Ptr Void
type FieldOptional "pNext" VkCommandBufferInheritanceInfo = 'False
type FieldOffset "pNext" VkCommandBufferInheritanceInfo =
(8)
{-# LINE 583 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "pNext" VkCommandBufferInheritanceInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
8)
{-# LINE 591 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkCommandBufferInheritanceInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferInheritanceInfo
-> FieldType "pNext" VkCommandBufferInheritanceInfo
getField VkCommandBufferInheritanceInfo
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferInheritanceInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferInheritanceInfo
-> Ptr VkCommandBufferInheritanceInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferInheritanceInfo
x) (Int
8))
{-# LINE 598 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferInheritanceInfo
-> IO (FieldType "pNext" VkCommandBufferInheritanceInfo)
readField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
8)
{-# LINE 602 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkCommandBufferInheritanceInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferInheritanceInfo
-> FieldType "pNext" VkCommandBufferInheritanceInfo -> IO ()
writeField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
8)
{-# LINE 608 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "renderPass" VkCommandBufferInheritanceInfo where
type FieldType "renderPass" VkCommandBufferInheritanceInfo =
VkRenderPass
type FieldOptional "renderPass" VkCommandBufferInheritanceInfo =
'True
type FieldOffset "renderPass" VkCommandBufferInheritanceInfo =
(16)
{-# LINE 617 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "renderPass" VkCommandBufferInheritanceInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 626 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "renderPass" VkCommandBufferInheritanceInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferInheritanceInfo
-> FieldType "renderPass" VkCommandBufferInheritanceInfo
getField VkCommandBufferInheritanceInfo
x
= IO VkRenderPass -> VkRenderPass
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkRenderPass
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferInheritanceInfo
-> Ptr VkCommandBufferInheritanceInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferInheritanceInfo
x) (Int
16))
{-# LINE 633 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferInheritanceInfo
-> IO (FieldType "renderPass" VkCommandBufferInheritanceInfo)
readField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkRenderPass
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
16)
{-# LINE 637 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "renderPass" VkCommandBufferInheritanceInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferInheritanceInfo
-> FieldType "renderPass" VkCommandBufferInheritanceInfo -> IO ()
writeField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> VkRenderPass -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
16)
{-# LINE 643 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "subpass" VkCommandBufferInheritanceInfo where
type FieldType "subpass" VkCommandBufferInheritanceInfo = Word32
type FieldOptional "subpass" VkCommandBufferInheritanceInfo =
'False
type FieldOffset "subpass" VkCommandBufferInheritanceInfo =
(24)
{-# LINE 651 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "subpass" VkCommandBufferInheritanceInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
24)
{-# LINE 659 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "subpass" VkCommandBufferInheritanceInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferInheritanceInfo
-> FieldType "subpass" VkCommandBufferInheritanceInfo
getField VkCommandBufferInheritanceInfo
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferInheritanceInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferInheritanceInfo
-> Ptr VkCommandBufferInheritanceInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferInheritanceInfo
x) (Int
24))
{-# LINE 666 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferInheritanceInfo
-> IO (FieldType "subpass" VkCommandBufferInheritanceInfo)
readField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
24)
{-# LINE 670 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "subpass" VkCommandBufferInheritanceInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferInheritanceInfo
-> FieldType "subpass" VkCommandBufferInheritanceInfo -> IO ()
writeField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
24)
{-# LINE 676 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "framebuffer" VkCommandBufferInheritanceInfo where
type FieldType "framebuffer" VkCommandBufferInheritanceInfo =
VkFramebuffer
type FieldOptional "framebuffer" VkCommandBufferInheritanceInfo =
'True
type FieldOffset "framebuffer" VkCommandBufferInheritanceInfo =
(32)
{-# LINE 685 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "framebuffer" VkCommandBufferInheritanceInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
32)
{-# LINE 694 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "framebuffer" VkCommandBufferInheritanceInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferInheritanceInfo
-> FieldType "framebuffer" VkCommandBufferInheritanceInfo
getField VkCommandBufferInheritanceInfo
x
= IO VkFramebuffer -> VkFramebuffer
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkFramebuffer
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferInheritanceInfo
-> Ptr VkCommandBufferInheritanceInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferInheritanceInfo
x) (Int
32))
{-# LINE 701 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferInheritanceInfo
-> IO (FieldType "framebuffer" VkCommandBufferInheritanceInfo)
readField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkFramebuffer
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
32)
{-# LINE 705 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "framebuffer" VkCommandBufferInheritanceInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferInheritanceInfo
-> FieldType "framebuffer" VkCommandBufferInheritanceInfo -> IO ()
writeField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> VkFramebuffer -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
32)
{-# LINE 711 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "occlusionQueryEnable" VkCommandBufferInheritanceInfo
where
type FieldType "occlusionQueryEnable"
VkCommandBufferInheritanceInfo
= VkBool32
type FieldOptional "occlusionQueryEnable"
VkCommandBufferInheritanceInfo
= 'False
type FieldOffset "occlusionQueryEnable"
VkCommandBufferInheritanceInfo
=
(40)
{-# LINE 725 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "occlusionQueryEnable"
VkCommandBufferInheritanceInfo
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
40)
{-# LINE 735 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "occlusionQueryEnable" VkCommandBufferInheritanceInfo
where
{-# NOINLINE getField #-}
getField :: VkCommandBufferInheritanceInfo
-> FieldType "occlusionQueryEnable" VkCommandBufferInheritanceInfo
getField VkCommandBufferInheritanceInfo
x
= IO VkBool32 -> VkBool32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferInheritanceInfo
-> Ptr VkCommandBufferInheritanceInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferInheritanceInfo
x) (Int
40))
{-# LINE 743 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferInheritanceInfo
-> IO
(FieldType "occlusionQueryEnable" VkCommandBufferInheritanceInfo)
readField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkBool32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
40)
{-# LINE 747 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "occlusionQueryEnable" VkCommandBufferInheritanceInfo
where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferInheritanceInfo
-> FieldType "occlusionQueryEnable" VkCommandBufferInheritanceInfo
-> IO ()
writeField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> VkBool32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
40)
{-# LINE 754 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "queryFlags" VkCommandBufferInheritanceInfo where
type FieldType "queryFlags" VkCommandBufferInheritanceInfo =
VkQueryControlFlags
type FieldOptional "queryFlags" VkCommandBufferInheritanceInfo =
'True
type FieldOffset "queryFlags" VkCommandBufferInheritanceInfo =
(44)
{-# LINE 763 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "queryFlags" VkCommandBufferInheritanceInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
44)
{-# LINE 772 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "queryFlags" VkCommandBufferInheritanceInfo where
{-# NOINLINE getField #-}
getField :: VkCommandBufferInheritanceInfo
-> FieldType "queryFlags" VkCommandBufferInheritanceInfo
getField VkCommandBufferInheritanceInfo
x
= IO VkQueryControlFlags -> VkQueryControlFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkQueryControlFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferInheritanceInfo
-> Ptr VkCommandBufferInheritanceInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferInheritanceInfo
x) (Int
44))
{-# LINE 779 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferInheritanceInfo
-> IO (FieldType "queryFlags" VkCommandBufferInheritanceInfo)
readField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo -> Int -> IO VkQueryControlFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
44)
{-# LINE 783 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "queryFlags" VkCommandBufferInheritanceInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferInheritanceInfo
-> FieldType "queryFlags" VkCommandBufferInheritanceInfo -> IO ()
writeField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo
-> Int -> VkQueryControlFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
44)
{-# LINE 789 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pipelineStatistics" VkCommandBufferInheritanceInfo where
type FieldType "pipelineStatistics" VkCommandBufferInheritanceInfo
= VkQueryPipelineStatisticFlags
type FieldOptional "pipelineStatistics"
VkCommandBufferInheritanceInfo
= 'True
type FieldOffset "pipelineStatistics"
VkCommandBufferInheritanceInfo
=
(48)
{-# LINE 801 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "pipelineStatistics"
VkCommandBufferInheritanceInfo
= 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
48)
{-# LINE 811 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pipelineStatistics" VkCommandBufferInheritanceInfo
where
{-# NOINLINE getField #-}
getField :: VkCommandBufferInheritanceInfo
-> FieldType "pipelineStatistics" VkCommandBufferInheritanceInfo
getField VkCommandBufferInheritanceInfo
x
= IO VkQueryPipelineStatisticFlags -> VkQueryPipelineStatisticFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandBufferInheritanceInfo
-> Int -> IO VkQueryPipelineStatisticFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandBufferInheritanceInfo
-> Ptr VkCommandBufferInheritanceInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandBufferInheritanceInfo
x) (Int
48))
{-# LINE 819 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandBufferInheritanceInfo
-> IO
(FieldType "pipelineStatistics" VkCommandBufferInheritanceInfo)
readField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo
-> Int -> IO VkQueryPipelineStatisticFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
48)
{-# LINE 823 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pipelineStatistics" VkCommandBufferInheritanceInfo
where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandBufferInheritanceInfo
-> FieldType "pipelineStatistics" VkCommandBufferInheritanceInfo
-> IO ()
writeField Ptr VkCommandBufferInheritanceInfo
p
= Ptr VkCommandBufferInheritanceInfo
-> Int -> VkQueryPipelineStatisticFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandBufferInheritanceInfo
p (Int
48)
{-# LINE 830 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance Show VkCommandBufferInheritanceInfo where
showsPrec :: Int -> VkCommandBufferInheritanceInfo -> ShowS
showsPrec Int
d VkCommandBufferInheritanceInfo
x
= String -> ShowS
showString String
"VkCommandBufferInheritanceInfo {" 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 (VkCommandBufferInheritanceInfo
-> FieldType "sType" VkCommandBufferInheritanceInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkCommandBufferInheritanceInfo
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 (VkCommandBufferInheritanceInfo
-> FieldType "pNext" VkCommandBufferInheritanceInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkCommandBufferInheritanceInfo
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
"renderPass = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkRenderPass -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCommandBufferInheritanceInfo
-> FieldType "renderPass" VkCommandBufferInheritanceInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"renderPass" VkCommandBufferInheritanceInfo
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
"subpass = " 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 (VkCommandBufferInheritanceInfo
-> FieldType "subpass" VkCommandBufferInheritanceInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"subpass" VkCommandBufferInheritanceInfo
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
"framebuffer = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkFramebuffer -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCommandBufferInheritanceInfo
-> FieldType "framebuffer" VkCommandBufferInheritanceInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"framebuffer" VkCommandBufferInheritanceInfo
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
"occlusionQueryEnable = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkBool32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCommandBufferInheritanceInfo
-> FieldType "occlusionQueryEnable" VkCommandBufferInheritanceInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"occlusionQueryEnable" VkCommandBufferInheritanceInfo
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
"queryFlags = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkQueryControlFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCommandBufferInheritanceInfo
-> FieldType "queryFlags" VkCommandBufferInheritanceInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"queryFlags" VkCommandBufferInheritanceInfo
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
"pipelineStatistics = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkQueryPipelineStatisticFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d
(VkCommandBufferInheritanceInfo
-> FieldType "pipelineStatistics" VkCommandBufferInheritanceInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pipelineStatistics" VkCommandBufferInheritanceInfo
x)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkCommandPoolCreateInfo = VkCommandPoolCreateInfo# Addr#
ByteArray#
instance Eq VkCommandPoolCreateInfo where
(VkCommandPoolCreateInfo# Addr#
a ByteArray#
_) == :: VkCommandPoolCreateInfo -> VkCommandPoolCreateInfo -> Bool
== x :: VkCommandPoolCreateInfo
x@(VkCommandPoolCreateInfo# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCommandPoolCreateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkCommandPoolCreateInfo
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkCommandPoolCreateInfo where
(VkCommandPoolCreateInfo# Addr#
a ByteArray#
_) compare :: VkCommandPoolCreateInfo -> VkCommandPoolCreateInfo -> Ordering
`compare`
x :: VkCommandPoolCreateInfo
x@(VkCommandPoolCreateInfo# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkCommandPoolCreateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkCommandPoolCreateInfo
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkCommandPoolCreateInfo where
sizeOf :: VkCommandPoolCreateInfo -> Int
sizeOf ~VkCommandPoolCreateInfo
_ = (Int
24)
{-# LINE 885 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkCommandPoolCreateInfo -> Int
alignment ~VkCommandPoolCreateInfo
_ = Int
8
{-# LINE 888 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkCommandPoolCreateInfo -> IO VkCommandPoolCreateInfo
peek = Ptr VkCommandPoolCreateInfo -> IO VkCommandPoolCreateInfo
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkCommandPoolCreateInfo -> VkCommandPoolCreateInfo -> IO ()
poke = Ptr VkCommandPoolCreateInfo -> VkCommandPoolCreateInfo -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkCommandPoolCreateInfo where
unsafeAddr :: VkCommandPoolCreateInfo -> Addr#
unsafeAddr (VkCommandPoolCreateInfo# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkCommandPoolCreateInfo -> ByteArray#
unsafeByteArray (VkCommandPoolCreateInfo# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkCommandPoolCreateInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkCommandPoolCreateInfo
VkCommandPoolCreateInfo# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkCommandPoolCreateInfo where
type StructFields VkCommandPoolCreateInfo =
'["sType", "pNext", "flags", "queueFamilyIndex"]
type CUnionType VkCommandPoolCreateInfo = 'False
type ReturnedOnly VkCommandPoolCreateInfo = 'False
type StructExtends VkCommandPoolCreateInfo = '[]
instance {-# OVERLAPPING #-}
HasField "sType" VkCommandPoolCreateInfo where
type FieldType "sType" VkCommandPoolCreateInfo = VkStructureType
type FieldOptional "sType" VkCommandPoolCreateInfo = 'False
type FieldOffset "sType" VkCommandPoolCreateInfo =
(0)
{-# LINE 922 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "sType" VkCommandPoolCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 929 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkCommandPoolCreateInfo where
{-# NOINLINE getField #-}
getField :: VkCommandPoolCreateInfo
-> FieldType "sType" VkCommandPoolCreateInfo
getField VkCommandPoolCreateInfo
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandPoolCreateInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandPoolCreateInfo -> Ptr VkCommandPoolCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandPoolCreateInfo
x) (Int
0))
{-# LINE 936 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandPoolCreateInfo
-> IO (FieldType "sType" VkCommandPoolCreateInfo)
readField Ptr VkCommandPoolCreateInfo
p
= Ptr VkCommandPoolCreateInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandPoolCreateInfo
p (Int
0)
{-# LINE 940 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkCommandPoolCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandPoolCreateInfo
-> FieldType "sType" VkCommandPoolCreateInfo -> IO ()
writeField Ptr VkCommandPoolCreateInfo
p
= Ptr VkCommandPoolCreateInfo -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandPoolCreateInfo
p (Int
0)
{-# LINE 946 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkCommandPoolCreateInfo where
type FieldType "pNext" VkCommandPoolCreateInfo = Ptr Void
type FieldOptional "pNext" VkCommandPoolCreateInfo = 'False
type FieldOffset "pNext" VkCommandPoolCreateInfo =
(8)
{-# LINE 953 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "pNext" VkCommandPoolCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 960 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkCommandPoolCreateInfo where
{-# NOINLINE getField #-}
getField :: VkCommandPoolCreateInfo
-> FieldType "pNext" VkCommandPoolCreateInfo
getField VkCommandPoolCreateInfo
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandPoolCreateInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandPoolCreateInfo -> Ptr VkCommandPoolCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandPoolCreateInfo
x) (Int
8))
{-# LINE 967 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandPoolCreateInfo
-> IO (FieldType "pNext" VkCommandPoolCreateInfo)
readField Ptr VkCommandPoolCreateInfo
p
= Ptr VkCommandPoolCreateInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandPoolCreateInfo
p (Int
8)
{-# LINE 971 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkCommandPoolCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandPoolCreateInfo
-> FieldType "pNext" VkCommandPoolCreateInfo -> IO ()
writeField Ptr VkCommandPoolCreateInfo
p
= Ptr VkCommandPoolCreateInfo -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandPoolCreateInfo
p (Int
8)
{-# LINE 977 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "flags" VkCommandPoolCreateInfo where
type FieldType "flags" VkCommandPoolCreateInfo =
VkCommandPoolCreateFlags
type FieldOptional "flags" VkCommandPoolCreateInfo = 'True
type FieldOffset "flags" VkCommandPoolCreateInfo =
(16)
{-# LINE 985 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "flags" VkCommandPoolCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
16)
{-# LINE 992 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "flags" VkCommandPoolCreateInfo where
{-# NOINLINE getField #-}
getField :: VkCommandPoolCreateInfo
-> FieldType "flags" VkCommandPoolCreateInfo
getField VkCommandPoolCreateInfo
x
= IO VkCommandPoolCreateFlags -> VkCommandPoolCreateFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandPoolCreateInfo -> Int -> IO VkCommandPoolCreateFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandPoolCreateInfo -> Ptr VkCommandPoolCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandPoolCreateInfo
x) (Int
16))
{-# LINE 999 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandPoolCreateInfo
-> IO (FieldType "flags" VkCommandPoolCreateInfo)
readField Ptr VkCommandPoolCreateInfo
p
= Ptr VkCommandPoolCreateInfo -> Int -> IO VkCommandPoolCreateFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandPoolCreateInfo
p (Int
16)
{-# LINE 1003 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "flags" VkCommandPoolCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandPoolCreateInfo
-> FieldType "flags" VkCommandPoolCreateInfo -> IO ()
writeField Ptr VkCommandPoolCreateInfo
p
= Ptr VkCommandPoolCreateInfo
-> Int -> VkCommandPoolCreateFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandPoolCreateInfo
p (Int
16)
{-# LINE 1009 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "queueFamilyIndex" VkCommandPoolCreateInfo where
type FieldType "queueFamilyIndex" VkCommandPoolCreateInfo = Word32
type FieldOptional "queueFamilyIndex" VkCommandPoolCreateInfo =
'False
type FieldOffset "queueFamilyIndex" VkCommandPoolCreateInfo =
(20)
{-# LINE 1017 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
type FieldIsArray "queueFamilyIndex" VkCommandPoolCreateInfo =
'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
20)
{-# LINE 1026 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "queueFamilyIndex" VkCommandPoolCreateInfo where
{-# NOINLINE getField #-}
getField :: VkCommandPoolCreateInfo
-> FieldType "queueFamilyIndex" VkCommandPoolCreateInfo
getField VkCommandPoolCreateInfo
x
= IO Word32 -> Word32
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkCommandPoolCreateInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkCommandPoolCreateInfo -> Ptr VkCommandPoolCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkCommandPoolCreateInfo
x) (Int
20))
{-# LINE 1033 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkCommandPoolCreateInfo
-> IO (FieldType "queueFamilyIndex" VkCommandPoolCreateInfo)
readField Ptr VkCommandPoolCreateInfo
p
= Ptr VkCommandPoolCreateInfo -> Int -> IO Word32
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkCommandPoolCreateInfo
p (Int
20)
{-# LINE 1037 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "queueFamilyIndex" VkCommandPoolCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkCommandPoolCreateInfo
-> FieldType "queueFamilyIndex" VkCommandPoolCreateInfo -> IO ()
writeField Ptr VkCommandPoolCreateInfo
p
= Ptr VkCommandPoolCreateInfo -> Int -> Word32 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkCommandPoolCreateInfo
p (Int
20)
{-# LINE 1043 "src-gen/Graphics/Vulkan/Types/Struct/Command.hsc" #-}
instance Show VkCommandPoolCreateInfo where
showsPrec :: Int -> VkCommandPoolCreateInfo -> ShowS
showsPrec Int
d VkCommandPoolCreateInfo
x
= String -> ShowS
showString String
"VkCommandPoolCreateInfo {" 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 (VkCommandPoolCreateInfo
-> FieldType "sType" VkCommandPoolCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkCommandPoolCreateInfo
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 (VkCommandPoolCreateInfo
-> FieldType "pNext" VkCommandPoolCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkCommandPoolCreateInfo
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 -> VkCommandPoolCreateFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkCommandPoolCreateInfo
-> FieldType "flags" VkCommandPoolCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkCommandPoolCreateInfo
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
"queueFamilyIndex = " 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 (VkCommandPoolCreateInfo
-> FieldType "queueFamilyIndex" VkCommandPoolCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"queueFamilyIndex" VkCommandPoolCreateInfo
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'