{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_external_semaphore_fd ( getSemaphoreFdKHR
, importSemaphoreFdKHR
, ImportSemaphoreFdInfoKHR(..)
, SemaphoreGetFdInfoKHR(..)
, KHR_EXTERNAL_SEMAPHORE_FD_SPEC_VERSION
, pattern KHR_EXTERNAL_SEMAPHORE_FD_SPEC_VERSION
, KHR_EXTERNAL_SEMAPHORE_FD_EXTENSION_NAME
, pattern KHR_EXTERNAL_SEMAPHORE_FD_EXTENSION_NAME
) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.Coerce (coerce)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Foreign.C.Types (CInt(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CInt)
import Foreign.C.Types (CInt(..))
import Foreign.C.Types (CInt(CInt))
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetSemaphoreFdKHR))
import Vulkan.Dynamic (DeviceCmds(pVkImportSemaphoreFdKHR))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core11.Enums.ExternalSemaphoreHandleTypeFlagBits (ExternalSemaphoreHandleTypeFlagBits)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Handles (Semaphore)
import Vulkan.Core11.Enums.SemaphoreImportFlagBits (SemaphoreImportFlags)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMPORT_SEMAPHORE_FD_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SEMAPHORE_GET_FD_INFO_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetSemaphoreFdKHR
:: FunPtr (Ptr Device_T -> Ptr SemaphoreGetFdInfoKHR -> Ptr CInt -> IO Result) -> Ptr Device_T -> Ptr SemaphoreGetFdInfoKHR -> Ptr CInt -> IO Result
getSemaphoreFdKHR :: forall io
. (MonadIO io)
=>
Device
->
SemaphoreGetFdInfoKHR
-> io (("fd" ::: Int32))
getSemaphoreFdKHR :: forall (io :: * -> *).
MonadIO io =>
Device -> SemaphoreGetFdInfoKHR -> io ("fd" ::: Int32)
getSemaphoreFdKHR Device
device SemaphoreGetFdInfoKHR
getFdInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkGetSemaphoreFdKHRPtr :: FunPtr
(Ptr Device_T
-> ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
vkGetSemaphoreFdKHRPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
pVkGetSemaphoreFdKHR (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
vkGetSemaphoreFdKHRPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetSemaphoreFdKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetSemaphoreFdKHR' :: Ptr Device_T
-> ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result
vkGetSemaphoreFdKHR' = FunPtr
(Ptr Device_T
-> ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
-> Ptr Device_T
-> ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result
mkVkGetSemaphoreFdKHR FunPtr
(Ptr Device_T
-> ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
vkGetSemaphoreFdKHRPtr
"pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
pGetFdInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (SemaphoreGetFdInfoKHR
getFdInfo)
"pFd" ::: Ptr CInt
pPFd <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @CInt Int
4) forall a. Ptr a -> IO ()
free
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetSemaphoreFdKHR" (Ptr Device_T
-> ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result
vkGetSemaphoreFdKHR'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
pGetFdInfo
("pFd" ::: Ptr CInt
pPFd))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
CInt
pFd <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @CInt "pFd" ::: Ptr CInt
pPFd
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ((coerce :: forall a b. Coercible a b => a -> b
coerce @CInt @Int32 CInt
pFd))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkImportSemaphoreFdKHR
:: FunPtr (Ptr Device_T -> Ptr ImportSemaphoreFdInfoKHR -> IO Result) -> Ptr Device_T -> Ptr ImportSemaphoreFdInfoKHR -> IO Result
importSemaphoreFdKHR :: forall io
. (MonadIO io)
=>
Device
->
ImportSemaphoreFdInfoKHR
-> io ()
importSemaphoreFdKHR :: forall (io :: * -> *).
MonadIO io =>
Device -> ImportSemaphoreFdInfoKHR -> io ()
importSemaphoreFdKHR Device
device ImportSemaphoreFdInfoKHR
importSemaphoreFdInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
let vkImportSemaphoreFdKHRPtr :: FunPtr
(Ptr Device_T
-> ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO Result)
vkImportSemaphoreFdKHRPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO Result)
pVkImportSemaphoreFdKHR (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO Result)
vkImportSemaphoreFdKHRPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkImportSemaphoreFdKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkImportSemaphoreFdKHR' :: Ptr Device_T
-> ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO Result
vkImportSemaphoreFdKHR' = FunPtr
(Ptr Device_T
-> ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO Result)
-> Ptr Device_T
-> ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO Result
mkVkImportSemaphoreFdKHR FunPtr
(Ptr Device_T
-> ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO Result)
vkImportSemaphoreFdKHRPtr
"pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
pImportSemaphoreFdInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ImportSemaphoreFdInfoKHR
importSemaphoreFdInfo)
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkImportSemaphoreFdKHR" (Ptr Device_T
-> ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO Result
vkImportSemaphoreFdKHR'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
pImportSemaphoreFdInfo)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
data ImportSemaphoreFdInfoKHR = ImportSemaphoreFdInfoKHR
{
ImportSemaphoreFdInfoKHR -> Semaphore
semaphore :: Semaphore
,
ImportSemaphoreFdInfoKHR -> SemaphoreImportFlags
flags :: SemaphoreImportFlags
,
ImportSemaphoreFdInfoKHR -> ExternalSemaphoreHandleTypeFlagBits
handleType :: ExternalSemaphoreHandleTypeFlagBits
,
ImportSemaphoreFdInfoKHR -> "fd" ::: Int32
fd :: Int32
}
deriving (Typeable, ImportSemaphoreFdInfoKHR -> ImportSemaphoreFdInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportSemaphoreFdInfoKHR -> ImportSemaphoreFdInfoKHR -> Bool
$c/= :: ImportSemaphoreFdInfoKHR -> ImportSemaphoreFdInfoKHR -> Bool
== :: ImportSemaphoreFdInfoKHR -> ImportSemaphoreFdInfoKHR -> Bool
$c== :: ImportSemaphoreFdInfoKHR -> ImportSemaphoreFdInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImportSemaphoreFdInfoKHR)
#endif
deriving instance Show ImportSemaphoreFdInfoKHR
instance ToCStruct ImportSemaphoreFdInfoKHR where
withCStruct :: forall b.
ImportSemaphoreFdInfoKHR
-> (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO b)
-> IO b
withCStruct ImportSemaphoreFdInfoKHR
x ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p ImportSemaphoreFdInfoKHR
x (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR) -> IO b
f "pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p)
pokeCStruct :: forall b.
("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> ImportSemaphoreFdInfoKHR -> IO b -> IO b
pokeCStruct "pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p ImportSemaphoreFdInfoKHR{"fd" ::: Int32
Semaphore
SemaphoreImportFlags
ExternalSemaphoreHandleTypeFlagBits
fd :: "fd" ::: Int32
handleType :: ExternalSemaphoreHandleTypeFlagBits
flags :: SemaphoreImportFlags
semaphore :: Semaphore
$sel:fd:ImportSemaphoreFdInfoKHR :: ImportSemaphoreFdInfoKHR -> "fd" ::: Int32
$sel:handleType:ImportSemaphoreFdInfoKHR :: ImportSemaphoreFdInfoKHR -> ExternalSemaphoreHandleTypeFlagBits
$sel:flags:ImportSemaphoreFdInfoKHR :: ImportSemaphoreFdInfoKHR -> SemaphoreImportFlags
$sel:semaphore:ImportSemaphoreFdInfoKHR :: ImportSemaphoreFdInfoKHR -> Semaphore
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_SEMAPHORE_FD_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Semaphore)) (Semaphore
semaphore)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr SemaphoreImportFlags)) (SemaphoreImportFlags
flags)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ExternalSemaphoreHandleTypeFlagBits)) (ExternalSemaphoreHandleTypeFlagBits
handleType)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CInt)) (("fd" ::: Int32) -> CInt
CInt ("fd" ::: Int32
fd))
IO b
f
cStructSize :: Int
cStructSize = Int
40
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO b -> IO b
pokeZeroCStruct "pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_SEMAPHORE_FD_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Semaphore)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ExternalSemaphoreHandleTypeFlagBits)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CInt)) (("fd" ::: Int32) -> CInt
CInt (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct ImportSemaphoreFdInfoKHR where
peekCStruct :: ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO ImportSemaphoreFdInfoKHR
peekCStruct "pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p = do
Semaphore
semaphore <- forall a. Storable a => Ptr a -> IO a
peek @Semaphore (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Semaphore))
SemaphoreImportFlags
flags <- forall a. Storable a => Ptr a -> IO a
peek @SemaphoreImportFlags (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr SemaphoreImportFlags))
ExternalSemaphoreHandleTypeFlagBits
handleType <- forall a. Storable a => Ptr a -> IO a
peek @ExternalSemaphoreHandleTypeFlagBits (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ExternalSemaphoreHandleTypeFlagBits))
CInt
fd <- forall a. Storable a => Ptr a -> IO a
peek @CInt (("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CInt))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Semaphore
-> SemaphoreImportFlags
-> ExternalSemaphoreHandleTypeFlagBits
-> ("fd" ::: Int32)
-> ImportSemaphoreFdInfoKHR
ImportSemaphoreFdInfoKHR
Semaphore
semaphore SemaphoreImportFlags
flags ExternalSemaphoreHandleTypeFlagBits
handleType (coerce :: forall a b. Coercible a b => a -> b
coerce @CInt @Int32 CInt
fd)
instance Storable ImportSemaphoreFdInfoKHR where
sizeOf :: ImportSemaphoreFdInfoKHR -> Int
sizeOf ~ImportSemaphoreFdInfoKHR
_ = Int
40
alignment :: ImportSemaphoreFdInfoKHR -> Int
alignment ~ImportSemaphoreFdInfoKHR
_ = Int
8
peek :: ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> IO ImportSemaphoreFdInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR)
-> ImportSemaphoreFdInfoKHR -> IO ()
poke "pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
ptr ImportSemaphoreFdInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pImportSemaphoreFdInfo" ::: Ptr ImportSemaphoreFdInfoKHR
ptr ImportSemaphoreFdInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImportSemaphoreFdInfoKHR where
zero :: ImportSemaphoreFdInfoKHR
zero = Semaphore
-> SemaphoreImportFlags
-> ExternalSemaphoreHandleTypeFlagBits
-> ("fd" ::: Int32)
-> ImportSemaphoreFdInfoKHR
ImportSemaphoreFdInfoKHR
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data SemaphoreGetFdInfoKHR = SemaphoreGetFdInfoKHR
{
SemaphoreGetFdInfoKHR -> Semaphore
semaphore :: Semaphore
,
SemaphoreGetFdInfoKHR -> ExternalSemaphoreHandleTypeFlagBits
handleType :: ExternalSemaphoreHandleTypeFlagBits
}
deriving (Typeable, SemaphoreGetFdInfoKHR -> SemaphoreGetFdInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemaphoreGetFdInfoKHR -> SemaphoreGetFdInfoKHR -> Bool
$c/= :: SemaphoreGetFdInfoKHR -> SemaphoreGetFdInfoKHR -> Bool
== :: SemaphoreGetFdInfoKHR -> SemaphoreGetFdInfoKHR -> Bool
$c== :: SemaphoreGetFdInfoKHR -> SemaphoreGetFdInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SemaphoreGetFdInfoKHR)
#endif
deriving instance Show SemaphoreGetFdInfoKHR
instance ToCStruct SemaphoreGetFdInfoKHR where
withCStruct :: forall b.
SemaphoreGetFdInfoKHR
-> (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR) -> IO b) -> IO b
withCStruct SemaphoreGetFdInfoKHR
x ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p SemaphoreGetFdInfoKHR
x (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR) -> IO b
f "pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p)
pokeCStruct :: forall b.
("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> SemaphoreGetFdInfoKHR -> IO b -> IO b
pokeCStruct "pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p SemaphoreGetFdInfoKHR{Semaphore
ExternalSemaphoreHandleTypeFlagBits
handleType :: ExternalSemaphoreHandleTypeFlagBits
semaphore :: Semaphore
$sel:handleType:SemaphoreGetFdInfoKHR :: SemaphoreGetFdInfoKHR -> ExternalSemaphoreHandleTypeFlagBits
$sel:semaphore:SemaphoreGetFdInfoKHR :: SemaphoreGetFdInfoKHR -> Semaphore
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SEMAPHORE_GET_FD_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Semaphore)) (Semaphore
semaphore)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalSemaphoreHandleTypeFlagBits)) (ExternalSemaphoreHandleTypeFlagBits
handleType)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR) -> IO b -> IO b
pokeZeroCStruct "pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SEMAPHORE_GET_FD_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Semaphore)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalSemaphoreHandleTypeFlagBits)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct SemaphoreGetFdInfoKHR where
peekCStruct :: ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> IO SemaphoreGetFdInfoKHR
peekCStruct "pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p = do
Semaphore
semaphore <- forall a. Storable a => Ptr a -> IO a
peek @Semaphore (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Semaphore))
ExternalSemaphoreHandleTypeFlagBits
handleType <- forall a. Storable a => Ptr a -> IO a
peek @ExternalSemaphoreHandleTypeFlagBits (("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalSemaphoreHandleTypeFlagBits))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Semaphore
-> ExternalSemaphoreHandleTypeFlagBits -> SemaphoreGetFdInfoKHR
SemaphoreGetFdInfoKHR
Semaphore
semaphore ExternalSemaphoreHandleTypeFlagBits
handleType
instance Storable SemaphoreGetFdInfoKHR where
sizeOf :: SemaphoreGetFdInfoKHR -> Int
sizeOf ~SemaphoreGetFdInfoKHR
_ = Int
32
alignment :: SemaphoreGetFdInfoKHR -> Int
alignment ~SemaphoreGetFdInfoKHR
_ = Int
8
peek :: ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> IO SemaphoreGetFdInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR)
-> SemaphoreGetFdInfoKHR -> IO ()
poke "pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
ptr SemaphoreGetFdInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pGetFdInfo" ::: Ptr SemaphoreGetFdInfoKHR
ptr SemaphoreGetFdInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SemaphoreGetFdInfoKHR where
zero :: SemaphoreGetFdInfoKHR
zero = Semaphore
-> ExternalSemaphoreHandleTypeFlagBits -> SemaphoreGetFdInfoKHR
SemaphoreGetFdInfoKHR
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type KHR_EXTERNAL_SEMAPHORE_FD_SPEC_VERSION = 1
pattern KHR_EXTERNAL_SEMAPHORE_FD_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_EXTERNAL_SEMAPHORE_FD_SPEC_VERSION :: forall a. Integral a => a
$mKHR_EXTERNAL_SEMAPHORE_FD_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_EXTERNAL_SEMAPHORE_FD_SPEC_VERSION = 1
type KHR_EXTERNAL_SEMAPHORE_FD_EXTENSION_NAME = "VK_KHR_external_semaphore_fd"
pattern KHR_EXTERNAL_SEMAPHORE_FD_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_EXTERNAL_SEMAPHORE_FD_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mKHR_EXTERNAL_SEMAPHORE_FD_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_EXTERNAL_SEMAPHORE_FD_EXTENSION_NAME = "VK_KHR_external_semaphore_fd"