{-# LINE 1 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE Strict #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
module Graphics.Vulkan.Types.Struct.Semaphore
(VkSemaphoreCreateInfo(..), VkSemaphoreGetFdInfoKHR(..)) 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 (VkSemaphoreCreateFlags)
import Graphics.Vulkan.Types.Enum.External (VkExternalSemaphoreHandleTypeFlagBits)
import Graphics.Vulkan.Types.Enum.StructureType (VkStructureType)
import Graphics.Vulkan.Types.Handles (VkSemaphore)
import System.IO.Unsafe (unsafeDupablePerformIO)
data VkSemaphoreCreateInfo = VkSemaphoreCreateInfo# Addr#
ByteArray#
instance Eq VkSemaphoreCreateInfo where
(VkSemaphoreCreateInfo# Addr#
a ByteArray#
_) == :: VkSemaphoreCreateInfo -> VkSemaphoreCreateInfo -> Bool
== x :: VkSemaphoreCreateInfo
x@(VkSemaphoreCreateInfo# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSemaphoreCreateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkSemaphoreCreateInfo
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSemaphoreCreateInfo where
(VkSemaphoreCreateInfo# Addr#
a ByteArray#
_) compare :: VkSemaphoreCreateInfo -> VkSemaphoreCreateInfo -> Ordering
`compare`
x :: VkSemaphoreCreateInfo
x@(VkSemaphoreCreateInfo# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSemaphoreCreateInfo -> Int
forall a. Storable a => a -> Int
sizeOf VkSemaphoreCreateInfo
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSemaphoreCreateInfo where
sizeOf :: VkSemaphoreCreateInfo -> Int
sizeOf ~VkSemaphoreCreateInfo
_ = (Int
24)
{-# LINE 48 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSemaphoreCreateInfo -> Int
alignment ~VkSemaphoreCreateInfo
_ = Int
8
{-# LINE 51 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSemaphoreCreateInfo -> IO VkSemaphoreCreateInfo
peek = Ptr VkSemaphoreCreateInfo -> IO VkSemaphoreCreateInfo
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSemaphoreCreateInfo -> VkSemaphoreCreateInfo -> IO ()
poke = Ptr VkSemaphoreCreateInfo -> VkSemaphoreCreateInfo -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSemaphoreCreateInfo where
unsafeAddr :: VkSemaphoreCreateInfo -> Addr#
unsafeAddr (VkSemaphoreCreateInfo# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSemaphoreCreateInfo -> ByteArray#
unsafeByteArray (VkSemaphoreCreateInfo# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSemaphoreCreateInfo
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSemaphoreCreateInfo
VkSemaphoreCreateInfo# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSemaphoreCreateInfo where
type StructFields VkSemaphoreCreateInfo =
'["sType", "pNext", "flags"]
type CUnionType VkSemaphoreCreateInfo = 'False
type ReturnedOnly VkSemaphoreCreateInfo = 'False
type StructExtends VkSemaphoreCreateInfo = '[]
instance {-# OVERLAPPING #-} HasField "sType" VkSemaphoreCreateInfo
where
type FieldType "sType" VkSemaphoreCreateInfo = VkStructureType
type FieldOptional "sType" VkSemaphoreCreateInfo = 'False
type FieldOffset "sType" VkSemaphoreCreateInfo =
(0)
{-# LINE 85 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
type FieldIsArray "sType" VkSemaphoreCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 92 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkSemaphoreCreateInfo where
{-# NOINLINE getField #-}
getField :: VkSemaphoreCreateInfo -> FieldType "sType" VkSemaphoreCreateInfo
getField VkSemaphoreCreateInfo
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSemaphoreCreateInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSemaphoreCreateInfo -> Ptr VkSemaphoreCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSemaphoreCreateInfo
x) (Int
0))
{-# LINE 99 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSemaphoreCreateInfo
-> IO (FieldType "sType" VkSemaphoreCreateInfo)
readField Ptr VkSemaphoreCreateInfo
p
= Ptr VkSemaphoreCreateInfo -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSemaphoreCreateInfo
p (Int
0)
{-# LINE 103 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkSemaphoreCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSemaphoreCreateInfo
-> FieldType "sType" VkSemaphoreCreateInfo -> IO ()
writeField Ptr VkSemaphoreCreateInfo
p
= Ptr VkSemaphoreCreateInfo -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSemaphoreCreateInfo
p (Int
0)
{-# LINE 109 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-} HasField "pNext" VkSemaphoreCreateInfo
where
type FieldType "pNext" VkSemaphoreCreateInfo = Ptr Void
type FieldOptional "pNext" VkSemaphoreCreateInfo = 'False
type FieldOffset "pNext" VkSemaphoreCreateInfo =
(8)
{-# LINE 116 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
type FieldIsArray "pNext" VkSemaphoreCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 123 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkSemaphoreCreateInfo where
{-# NOINLINE getField #-}
getField :: VkSemaphoreCreateInfo -> FieldType "pNext" VkSemaphoreCreateInfo
getField VkSemaphoreCreateInfo
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSemaphoreCreateInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSemaphoreCreateInfo -> Ptr VkSemaphoreCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSemaphoreCreateInfo
x) (Int
8))
{-# LINE 130 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSemaphoreCreateInfo
-> IO (FieldType "pNext" VkSemaphoreCreateInfo)
readField Ptr VkSemaphoreCreateInfo
p
= Ptr VkSemaphoreCreateInfo -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSemaphoreCreateInfo
p (Int
8)
{-# LINE 134 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkSemaphoreCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSemaphoreCreateInfo
-> FieldType "pNext" VkSemaphoreCreateInfo -> IO ()
writeField Ptr VkSemaphoreCreateInfo
p
= Ptr VkSemaphoreCreateInfo -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSemaphoreCreateInfo
p (Int
8)
{-# LINE 140 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-} HasField "flags" VkSemaphoreCreateInfo
where
type FieldType "flags" VkSemaphoreCreateInfo =
VkSemaphoreCreateFlags
type FieldOptional "flags" VkSemaphoreCreateInfo = 'True
type FieldOffset "flags" VkSemaphoreCreateInfo =
(16)
{-# LINE 148 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
type FieldIsArray "flags" VkSemaphoreCreateInfo = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
True
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
16)
{-# LINE 155 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "flags" VkSemaphoreCreateInfo where
{-# NOINLINE getField #-}
getField :: VkSemaphoreCreateInfo -> FieldType "flags" VkSemaphoreCreateInfo
getField VkSemaphoreCreateInfo
x
= IO VkSemaphoreCreateFlags -> VkSemaphoreCreateFlags
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSemaphoreCreateInfo -> Int -> IO VkSemaphoreCreateFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSemaphoreCreateInfo -> Ptr VkSemaphoreCreateInfo
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSemaphoreCreateInfo
x) (Int
16))
{-# LINE 162 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSemaphoreCreateInfo
-> IO (FieldType "flags" VkSemaphoreCreateInfo)
readField Ptr VkSemaphoreCreateInfo
p
= Ptr VkSemaphoreCreateInfo -> Int -> IO VkSemaphoreCreateFlags
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSemaphoreCreateInfo
p (Int
16)
{-# LINE 166 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "flags" VkSemaphoreCreateInfo where
{-# INLINE writeField #-}
writeField :: Ptr VkSemaphoreCreateInfo
-> FieldType "flags" VkSemaphoreCreateInfo -> IO ()
writeField Ptr VkSemaphoreCreateInfo
p
= Ptr VkSemaphoreCreateInfo -> Int -> VkSemaphoreCreateFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSemaphoreCreateInfo
p (Int
16)
{-# LINE 172 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance Show VkSemaphoreCreateInfo where
showsPrec :: Int -> VkSemaphoreCreateInfo -> ShowS
showsPrec Int
d VkSemaphoreCreateInfo
x
= String -> ShowS
showString String
"VkSemaphoreCreateInfo {" 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 (VkSemaphoreCreateInfo -> FieldType "sType" VkSemaphoreCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkSemaphoreCreateInfo
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 (VkSemaphoreCreateInfo -> FieldType "pNext" VkSemaphoreCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkSemaphoreCreateInfo
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 -> VkSemaphoreCreateFlags -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSemaphoreCreateInfo -> FieldType "flags" VkSemaphoreCreateInfo
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"flags" VkSemaphoreCreateInfo
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'
data VkSemaphoreGetFdInfoKHR = VkSemaphoreGetFdInfoKHR# Addr#
ByteArray#
instance Eq VkSemaphoreGetFdInfoKHR where
(VkSemaphoreGetFdInfoKHR# Addr#
a ByteArray#
_) == :: VkSemaphoreGetFdInfoKHR -> VkSemaphoreGetFdInfoKHR -> Bool
== x :: VkSemaphoreGetFdInfoKHR
x@(VkSemaphoreGetFdInfoKHR# Addr#
b ByteArray#
_)
= Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSemaphoreGetFdInfoKHR -> Int
forall a. Storable a => a -> Int
sizeOf VkSemaphoreGetFdInfoKHR
x) Addr#
a Addr#
b
{-# INLINE (==) #-}
instance Ord VkSemaphoreGetFdInfoKHR where
(VkSemaphoreGetFdInfoKHR# Addr#
a ByteArray#
_) compare :: VkSemaphoreGetFdInfoKHR -> VkSemaphoreGetFdInfoKHR -> Ordering
`compare`
x :: VkSemaphoreGetFdInfoKHR
x@(VkSemaphoreGetFdInfoKHR# Addr#
b ByteArray#
_) = Int -> Addr# -> Addr# -> Ordering
cmpBytes# (VkSemaphoreGetFdInfoKHR -> Int
forall a. Storable a => a -> Int
sizeOf VkSemaphoreGetFdInfoKHR
x) Addr#
a Addr#
b
{-# INLINE compare #-}
instance Storable VkSemaphoreGetFdInfoKHR where
sizeOf :: VkSemaphoreGetFdInfoKHR -> Int
sizeOf ~VkSemaphoreGetFdInfoKHR
_ = (Int
32)
{-# LINE 210 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE sizeOf #-}
alignment :: VkSemaphoreGetFdInfoKHR -> Int
alignment ~VkSemaphoreGetFdInfoKHR
_ = Int
8
{-# LINE 213 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE alignment #-}
peek :: Ptr VkSemaphoreGetFdInfoKHR -> IO VkSemaphoreGetFdInfoKHR
peek = Ptr VkSemaphoreGetFdInfoKHR -> IO VkSemaphoreGetFdInfoKHR
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> IO a
peekVkData#
{-# INLINE peek #-}
poke :: Ptr VkSemaphoreGetFdInfoKHR -> VkSemaphoreGetFdInfoKHR -> IO ()
poke = Ptr VkSemaphoreGetFdInfoKHR -> VkSemaphoreGetFdInfoKHR -> IO ()
forall a. (Storable a, VulkanMarshalPrim a) => Ptr a -> a -> IO ()
pokeVkData#
{-# INLINE poke #-}
instance VulkanMarshalPrim VkSemaphoreGetFdInfoKHR where
unsafeAddr :: VkSemaphoreGetFdInfoKHR -> Addr#
unsafeAddr (VkSemaphoreGetFdInfoKHR# Addr#
a ByteArray#
_) = Addr#
a
{-# INLINE unsafeAddr #-}
unsafeByteArray :: VkSemaphoreGetFdInfoKHR -> ByteArray#
unsafeByteArray (VkSemaphoreGetFdInfoKHR# Addr#
_ ByteArray#
b) = ByteArray#
b
{-# INLINE unsafeByteArray #-}
unsafeFromByteArrayOffset :: Int# -> ByteArray# -> VkSemaphoreGetFdInfoKHR
unsafeFromByteArrayOffset Int#
off ByteArray#
b
= Addr# -> ByteArray# -> VkSemaphoreGetFdInfoKHR
VkSemaphoreGetFdInfoKHR# (Addr# -> Int# -> Addr#
plusAddr# (ByteArray# -> Addr#
byteArrayContents# ByteArray#
b) Int#
off) ByteArray#
b
{-# INLINE unsafeFromByteArrayOffset #-}
instance VulkanMarshal VkSemaphoreGetFdInfoKHR where
type StructFields VkSemaphoreGetFdInfoKHR =
'["sType", "pNext", "semaphore", "handleType"]
type CUnionType VkSemaphoreGetFdInfoKHR = 'False
type ReturnedOnly VkSemaphoreGetFdInfoKHR = 'False
type StructExtends VkSemaphoreGetFdInfoKHR = '[]
instance {-# OVERLAPPING #-}
HasField "sType" VkSemaphoreGetFdInfoKHR where
type FieldType "sType" VkSemaphoreGetFdInfoKHR = VkStructureType
type FieldOptional "sType" VkSemaphoreGetFdInfoKHR = 'False
type FieldOffset "sType" VkSemaphoreGetFdInfoKHR =
(0)
{-# LINE 247 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
type FieldIsArray "sType" VkSemaphoreGetFdInfoKHR = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
0)
{-# LINE 254 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "sType" VkSemaphoreGetFdInfoKHR where
{-# NOINLINE getField #-}
getField :: VkSemaphoreGetFdInfoKHR
-> FieldType "sType" VkSemaphoreGetFdInfoKHR
getField VkSemaphoreGetFdInfoKHR
x
= IO VkStructureType -> VkStructureType
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSemaphoreGetFdInfoKHR -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSemaphoreGetFdInfoKHR -> Ptr VkSemaphoreGetFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSemaphoreGetFdInfoKHR
x) (Int
0))
{-# LINE 261 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSemaphoreGetFdInfoKHR
-> IO (FieldType "sType" VkSemaphoreGetFdInfoKHR)
readField Ptr VkSemaphoreGetFdInfoKHR
p
= Ptr VkSemaphoreGetFdInfoKHR -> Int -> IO VkStructureType
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSemaphoreGetFdInfoKHR
p (Int
0)
{-# LINE 265 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "sType" VkSemaphoreGetFdInfoKHR where
{-# INLINE writeField #-}
writeField :: Ptr VkSemaphoreGetFdInfoKHR
-> FieldType "sType" VkSemaphoreGetFdInfoKHR -> IO ()
writeField Ptr VkSemaphoreGetFdInfoKHR
p
= Ptr VkSemaphoreGetFdInfoKHR -> Int -> VkStructureType -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSemaphoreGetFdInfoKHR
p (Int
0)
{-# LINE 271 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "pNext" VkSemaphoreGetFdInfoKHR where
type FieldType "pNext" VkSemaphoreGetFdInfoKHR = Ptr Void
type FieldOptional "pNext" VkSemaphoreGetFdInfoKHR = 'False
type FieldOffset "pNext" VkSemaphoreGetFdInfoKHR =
(8)
{-# LINE 278 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
type FieldIsArray "pNext" VkSemaphoreGetFdInfoKHR = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset = (Int
8)
{-# LINE 285 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "pNext" VkSemaphoreGetFdInfoKHR where
{-# NOINLINE getField #-}
getField :: VkSemaphoreGetFdInfoKHR
-> FieldType "pNext" VkSemaphoreGetFdInfoKHR
getField VkSemaphoreGetFdInfoKHR
x
= IO (Ptr Void) -> Ptr Void
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSemaphoreGetFdInfoKHR -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSemaphoreGetFdInfoKHR -> Ptr VkSemaphoreGetFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSemaphoreGetFdInfoKHR
x) (Int
8))
{-# LINE 292 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSemaphoreGetFdInfoKHR
-> IO (FieldType "pNext" VkSemaphoreGetFdInfoKHR)
readField Ptr VkSemaphoreGetFdInfoKHR
p
= Ptr VkSemaphoreGetFdInfoKHR -> Int -> IO (Ptr Void)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSemaphoreGetFdInfoKHR
p (Int
8)
{-# LINE 296 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "pNext" VkSemaphoreGetFdInfoKHR where
{-# INLINE writeField #-}
writeField :: Ptr VkSemaphoreGetFdInfoKHR
-> FieldType "pNext" VkSemaphoreGetFdInfoKHR -> IO ()
writeField Ptr VkSemaphoreGetFdInfoKHR
p
= Ptr VkSemaphoreGetFdInfoKHR -> Int -> Ptr Void -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSemaphoreGetFdInfoKHR
p (Int
8)
{-# LINE 302 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "semaphore" VkSemaphoreGetFdInfoKHR where
type FieldType "semaphore" VkSemaphoreGetFdInfoKHR = VkSemaphore
type FieldOptional "semaphore" VkSemaphoreGetFdInfoKHR = 'False
type FieldOffset "semaphore" VkSemaphoreGetFdInfoKHR =
(16)
{-# LINE 309 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
type FieldIsArray "semaphore" VkSemaphoreGetFdInfoKHR = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
16)
{-# LINE 317 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "semaphore" VkSemaphoreGetFdInfoKHR where
{-# NOINLINE getField #-}
getField :: VkSemaphoreGetFdInfoKHR
-> FieldType "semaphore" VkSemaphoreGetFdInfoKHR
getField VkSemaphoreGetFdInfoKHR
x
= IO VkSemaphore -> VkSemaphore
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSemaphoreGetFdInfoKHR -> Int -> IO VkSemaphore
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSemaphoreGetFdInfoKHR -> Ptr VkSemaphoreGetFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSemaphoreGetFdInfoKHR
x) (Int
16))
{-# LINE 324 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSemaphoreGetFdInfoKHR
-> IO (FieldType "semaphore" VkSemaphoreGetFdInfoKHR)
readField Ptr VkSemaphoreGetFdInfoKHR
p
= Ptr VkSemaphoreGetFdInfoKHR -> Int -> IO VkSemaphore
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSemaphoreGetFdInfoKHR
p (Int
16)
{-# LINE 328 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "semaphore" VkSemaphoreGetFdInfoKHR where
{-# INLINE writeField #-}
writeField :: Ptr VkSemaphoreGetFdInfoKHR
-> FieldType "semaphore" VkSemaphoreGetFdInfoKHR -> IO ()
writeField Ptr VkSemaphoreGetFdInfoKHR
p
= Ptr VkSemaphoreGetFdInfoKHR -> Int -> VkSemaphore -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSemaphoreGetFdInfoKHR
p (Int
16)
{-# LINE 334 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
HasField "handleType" VkSemaphoreGetFdInfoKHR where
type FieldType "handleType" VkSemaphoreGetFdInfoKHR =
VkExternalSemaphoreHandleTypeFlagBits
type FieldOptional "handleType" VkSemaphoreGetFdInfoKHR = 'False
type FieldOffset "handleType" VkSemaphoreGetFdInfoKHR =
(24)
{-# LINE 342 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
type FieldIsArray "handleType" VkSemaphoreGetFdInfoKHR = 'False
{-# INLINE fieldOptional #-}
fieldOptional :: Bool
fieldOptional = Bool
False
{-# INLINE fieldOffset #-}
fieldOffset :: Int
fieldOffset
= (Int
24)
{-# LINE 350 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanReadField "handleType" VkSemaphoreGetFdInfoKHR where
{-# NOINLINE getField #-}
getField :: VkSemaphoreGetFdInfoKHR
-> FieldType "handleType" VkSemaphoreGetFdInfoKHR
getField VkSemaphoreGetFdInfoKHR
x
= IO VkExternalSemaphoreHandleTypeFlagBits
-> VkExternalSemaphoreHandleTypeFlagBits
forall a. IO a -> a
unsafeDupablePerformIO
(Ptr VkSemaphoreGetFdInfoKHR
-> Int -> IO VkExternalSemaphoreHandleTypeFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff (VkSemaphoreGetFdInfoKHR -> Ptr VkSemaphoreGetFdInfoKHR
forall a. VulkanMarshal a => a -> Ptr a
unsafePtr VkSemaphoreGetFdInfoKHR
x) (Int
24))
{-# LINE 357 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
{-# INLINE readField #-}
readField :: Ptr VkSemaphoreGetFdInfoKHR
-> IO (FieldType "handleType" VkSemaphoreGetFdInfoKHR)
readField Ptr VkSemaphoreGetFdInfoKHR
p
= Ptr VkSemaphoreGetFdInfoKHR
-> Int -> IO VkExternalSemaphoreHandleTypeFlagBits
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr VkSemaphoreGetFdInfoKHR
p (Int
24)
{-# LINE 361 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance {-# OVERLAPPING #-}
CanWriteField "handleType" VkSemaphoreGetFdInfoKHR where
{-# INLINE writeField #-}
writeField :: Ptr VkSemaphoreGetFdInfoKHR
-> FieldType "handleType" VkSemaphoreGetFdInfoKHR -> IO ()
writeField Ptr VkSemaphoreGetFdInfoKHR
p
= Ptr VkSemaphoreGetFdInfoKHR
-> Int -> VkExternalSemaphoreHandleTypeFlagBits -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr VkSemaphoreGetFdInfoKHR
p (Int
24)
{-# LINE 367 "src-gen/Graphics/Vulkan/Types/Struct/Semaphore.hsc" #-}
instance Show VkSemaphoreGetFdInfoKHR where
showsPrec :: Int -> VkSemaphoreGetFdInfoKHR -> ShowS
showsPrec Int
d VkSemaphoreGetFdInfoKHR
x
= String -> ShowS
showString String
"VkSemaphoreGetFdInfoKHR {" 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 (VkSemaphoreGetFdInfoKHR
-> FieldType "sType" VkSemaphoreGetFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"sType" VkSemaphoreGetFdInfoKHR
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 (VkSemaphoreGetFdInfoKHR
-> FieldType "pNext" VkSemaphoreGetFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"pNext" VkSemaphoreGetFdInfoKHR
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
"semaphore = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkSemaphore -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSemaphoreGetFdInfoKHR
-> FieldType "semaphore" VkSemaphoreGetFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"semaphore" VkSemaphoreGetFdInfoKHR
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
"handleType = " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Int -> VkExternalSemaphoreHandleTypeFlagBits -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d (VkSemaphoreGetFdInfoKHR
-> FieldType "handleType" VkSemaphoreGetFdInfoKHR
forall (fname :: Symbol) a.
CanReadField fname a =>
a -> FieldType fname a
getField @"handleType" VkSemaphoreGetFdInfoKHR
x) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'}'