{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_external_fence_win32 ( getFenceWin32HandleKHR
, importFenceWin32HandleKHR
, ImportFenceWin32HandleInfoKHR(..)
, ExportFenceWin32HandleInfoKHR(..)
, FenceGetWin32HandleInfoKHR(..)
, KHR_EXTERNAL_FENCE_WIN32_SPEC_VERSION
, pattern KHR_EXTERNAL_FENCE_WIN32_SPEC_VERSION
, KHR_EXTERNAL_FENCE_WIN32_EXTENSION_NAME
, pattern KHR_EXTERNAL_FENCE_WIN32_EXTENSION_NAME
, HANDLE
, DWORD
, LPCWSTR
, SECURITY_ATTRIBUTES
) 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 Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
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.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 Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Extensions.VK_NV_external_memory_win32 (DWORD)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetFenceWin32HandleKHR))
import Vulkan.Dynamic (DeviceCmds(pVkImportFenceWin32HandleKHR))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core11.Enums.ExternalFenceHandleTypeFlagBits (ExternalFenceHandleTypeFlagBits)
import Vulkan.Core10.Handles (Fence)
import Vulkan.Core11.Enums.FenceImportFlagBits (FenceImportFlags)
import Vulkan.Extensions.VK_NV_external_memory_win32 (HANDLE)
import Vulkan.Extensions.VK_KHR_external_memory_win32 (LPCWSTR)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Extensions.VK_NV_external_memory_win32 (SECURITY_ATTRIBUTES)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_EXPORT_FENCE_WIN32_HANDLE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FENCE_GET_WIN32_HANDLE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMPORT_FENCE_WIN32_HANDLE_INFO_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_NV_external_memory_win32 (DWORD)
import Vulkan.Extensions.VK_NV_external_memory_win32 (HANDLE)
import Vulkan.Extensions.VK_KHR_external_memory_win32 (LPCWSTR)
import Vulkan.Extensions.VK_NV_external_memory_win32 (SECURITY_ATTRIBUTES)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetFenceWin32HandleKHR
:: FunPtr (Ptr Device_T -> Ptr FenceGetWin32HandleInfoKHR -> Ptr HANDLE -> IO Result) -> Ptr Device_T -> Ptr FenceGetWin32HandleInfoKHR -> Ptr HANDLE -> IO Result
getFenceWin32HandleKHR :: forall io
. (MonadIO io)
=>
Device
->
FenceGetWin32HandleInfoKHR
-> io (HANDLE)
getFenceWin32HandleKHR :: forall (io :: * -> *).
MonadIO io =>
Device -> FenceGetWin32HandleInfoKHR -> io HANDLE
getFenceWin32HandleKHR Device
device FenceGetWin32HandleInfoKHR
getWin32HandleInfo = 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 vkGetFenceWin32HandleKHRPtr :: FunPtr
(Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result)
vkGetFenceWin32HandleKHRPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result)
pVkGetFenceWin32HandleKHR (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
-> ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result)
vkGetFenceWin32HandleKHRPtr 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 vkGetFenceWin32HandleKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetFenceWin32HandleKHR' :: Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result
vkGetFenceWin32HandleKHR' = FunPtr
(Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result)
-> Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result
mkVkGetFenceWin32HandleKHR FunPtr
(Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result)
vkGetFenceWin32HandleKHRPtr
"pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
pGetWin32HandleInfo <- 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 (FenceGetWin32HandleInfoKHR
getWin32HandleInfo)
"pHandle" ::: Ptr HANDLE
pPHandle <- 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 @HANDLE Int
8) 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
"vkGetFenceWin32HandleKHR" (Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result
vkGetFenceWin32HandleKHR'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
pGetWin32HandleInfo
("pHandle" ::: Ptr HANDLE
pPHandle))
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))
HANDLE
pHandle <- 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 @HANDLE "pHandle" ::: Ptr HANDLE
pPHandle
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (HANDLE
pHandle)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkImportFenceWin32HandleKHR
:: FunPtr (Ptr Device_T -> Ptr ImportFenceWin32HandleInfoKHR -> IO Result) -> Ptr Device_T -> Ptr ImportFenceWin32HandleInfoKHR -> IO Result
importFenceWin32HandleKHR :: forall io
. (MonadIO io)
=>
Device
->
ImportFenceWin32HandleInfoKHR
-> io ()
importFenceWin32HandleKHR :: forall (io :: * -> *).
MonadIO io =>
Device -> ImportFenceWin32HandleInfoKHR -> io ()
importFenceWin32HandleKHR Device
device
ImportFenceWin32HandleInfoKHR
importFenceWin32HandleInfo = 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 vkImportFenceWin32HandleKHRPtr :: FunPtr
(Ptr Device_T
-> ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO Result)
vkImportFenceWin32HandleKHRPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO Result)
pVkImportFenceWin32HandleKHR (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
-> ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO Result)
vkImportFenceWin32HandleKHRPtr 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 vkImportFenceWin32HandleKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkImportFenceWin32HandleKHR' :: Ptr Device_T
-> ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO Result
vkImportFenceWin32HandleKHR' = FunPtr
(Ptr Device_T
-> ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO Result)
-> Ptr Device_T
-> ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO Result
mkVkImportFenceWin32HandleKHR FunPtr
(Ptr Device_T
-> ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO Result)
vkImportFenceWin32HandleKHRPtr
"pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
pImportFenceWin32HandleInfo <- 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 (ImportFenceWin32HandleInfoKHR
importFenceWin32HandleInfo)
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
"vkImportFenceWin32HandleKHR" (Ptr Device_T
-> ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO Result
vkImportFenceWin32HandleKHR'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
pImportFenceWin32HandleInfo)
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 ImportFenceWin32HandleInfoKHR = ImportFenceWin32HandleInfoKHR
{
ImportFenceWin32HandleInfoKHR -> Fence
fence :: Fence
,
ImportFenceWin32HandleInfoKHR -> FenceImportFlags
flags :: FenceImportFlags
,
ImportFenceWin32HandleInfoKHR -> ExternalFenceHandleTypeFlagBits
handleType :: ExternalFenceHandleTypeFlagBits
,
ImportFenceWin32HandleInfoKHR -> HANDLE
handle :: HANDLE
,
ImportFenceWin32HandleInfoKHR -> LPCWSTR
name :: LPCWSTR
}
deriving (Typeable, ImportFenceWin32HandleInfoKHR
-> ImportFenceWin32HandleInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportFenceWin32HandleInfoKHR
-> ImportFenceWin32HandleInfoKHR -> Bool
$c/= :: ImportFenceWin32HandleInfoKHR
-> ImportFenceWin32HandleInfoKHR -> Bool
== :: ImportFenceWin32HandleInfoKHR
-> ImportFenceWin32HandleInfoKHR -> Bool
$c== :: ImportFenceWin32HandleInfoKHR
-> ImportFenceWin32HandleInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImportFenceWin32HandleInfoKHR)
#endif
deriving instance Show ImportFenceWin32HandleInfoKHR
instance ToCStruct ImportFenceWin32HandleInfoKHR where
withCStruct :: forall b.
ImportFenceWin32HandleInfoKHR
-> (("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO b)
-> IO b
withCStruct ImportFenceWin32HandleInfoKHR
x ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
48 forall a b. (a -> b) -> a -> b
$ \"pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p ImportFenceWin32HandleInfoKHR
x (("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO b
f "pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p)
pokeCStruct :: forall b.
("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> ImportFenceWin32HandleInfoKHR -> IO b -> IO b
pokeCStruct "pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p ImportFenceWin32HandleInfoKHR{HANDLE
LPCWSTR
Fence
FenceImportFlags
ExternalFenceHandleTypeFlagBits
name :: LPCWSTR
handle :: HANDLE
handleType :: ExternalFenceHandleTypeFlagBits
flags :: FenceImportFlags
fence :: Fence
$sel:name:ImportFenceWin32HandleInfoKHR :: ImportFenceWin32HandleInfoKHR -> LPCWSTR
$sel:handle:ImportFenceWin32HandleInfoKHR :: ImportFenceWin32HandleInfoKHR -> HANDLE
$sel:handleType:ImportFenceWin32HandleInfoKHR :: ImportFenceWin32HandleInfoKHR -> ExternalFenceHandleTypeFlagBits
$sel:flags:ImportFenceWin32HandleInfoKHR :: ImportFenceWin32HandleInfoKHR -> FenceImportFlags
$sel:fence:ImportFenceWin32HandleInfoKHR :: ImportFenceWin32HandleInfoKHR -> Fence
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_FENCE_WIN32_HANDLE_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
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 (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Fence)) (Fence
fence)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr FenceImportFlags)) (FenceImportFlags
flags)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ExternalFenceHandleTypeFlagBits)) (ExternalFenceHandleTypeFlagBits
handleType)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr HANDLE)) (HANDLE
handle)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr LPCWSTR)) (LPCWSTR
name)
IO b
f
cStructSize :: Int
cStructSize = Int
48
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO b -> IO b
pokeZeroCStruct "pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_FENCE_WIN32_HANDLE_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
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 (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Fence)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ExternalFenceHandleTypeFlagBits)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ImportFenceWin32HandleInfoKHR where
peekCStruct :: ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO ImportFenceWin32HandleInfoKHR
peekCStruct "pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p = do
Fence
fence <- forall a. Storable a => Ptr a -> IO a
peek @Fence (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Fence))
FenceImportFlags
flags <- forall a. Storable a => Ptr a -> IO a
peek @FenceImportFlags (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr FenceImportFlags))
ExternalFenceHandleTypeFlagBits
handleType <- forall a. Storable a => Ptr a -> IO a
peek @ExternalFenceHandleTypeFlagBits (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
28 :: Ptr ExternalFenceHandleTypeFlagBits))
HANDLE
handle <- forall a. Storable a => Ptr a -> IO a
peek @HANDLE (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr HANDLE))
LPCWSTR
name <- forall a. Storable a => Ptr a -> IO a
peek @LPCWSTR (("pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr LPCWSTR))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Fence
-> FenceImportFlags
-> ExternalFenceHandleTypeFlagBits
-> HANDLE
-> LPCWSTR
-> ImportFenceWin32HandleInfoKHR
ImportFenceWin32HandleInfoKHR
Fence
fence FenceImportFlags
flags ExternalFenceHandleTypeFlagBits
handleType HANDLE
handle LPCWSTR
name
instance Storable ImportFenceWin32HandleInfoKHR where
sizeOf :: ImportFenceWin32HandleInfoKHR -> Int
sizeOf ~ImportFenceWin32HandleInfoKHR
_ = Int
48
alignment :: ImportFenceWin32HandleInfoKHR -> Int
alignment ~ImportFenceWin32HandleInfoKHR
_ = Int
8
peek :: ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> IO ImportFenceWin32HandleInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pImportFenceWin32HandleInfo"
::: Ptr ImportFenceWin32HandleInfoKHR)
-> ImportFenceWin32HandleInfoKHR -> IO ()
poke "pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
ptr ImportFenceWin32HandleInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pImportFenceWin32HandleInfo" ::: Ptr ImportFenceWin32HandleInfoKHR
ptr ImportFenceWin32HandleInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImportFenceWin32HandleInfoKHR where
zero :: ImportFenceWin32HandleInfoKHR
zero = Fence
-> FenceImportFlags
-> ExternalFenceHandleTypeFlagBits
-> HANDLE
-> LPCWSTR
-> ImportFenceWin32HandleInfoKHR
ImportFenceWin32HandleInfoKHR
forall a. Zero a => a
zero
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 ExportFenceWin32HandleInfoKHR = ExportFenceWin32HandleInfoKHR
{
ExportFenceWin32HandleInfoKHR -> Ptr SECURITY_ATTRIBUTES
attributes :: Ptr SECURITY_ATTRIBUTES
,
ExportFenceWin32HandleInfoKHR -> DWORD
dwAccess :: DWORD
,
ExportFenceWin32HandleInfoKHR -> LPCWSTR
name :: LPCWSTR
}
deriving (Typeable, ExportFenceWin32HandleInfoKHR
-> ExportFenceWin32HandleInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportFenceWin32HandleInfoKHR
-> ExportFenceWin32HandleInfoKHR -> Bool
$c/= :: ExportFenceWin32HandleInfoKHR
-> ExportFenceWin32HandleInfoKHR -> Bool
== :: ExportFenceWin32HandleInfoKHR
-> ExportFenceWin32HandleInfoKHR -> Bool
$c== :: ExportFenceWin32HandleInfoKHR
-> ExportFenceWin32HandleInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ExportFenceWin32HandleInfoKHR)
#endif
deriving instance Show ExportFenceWin32HandleInfoKHR
instance ToCStruct ExportFenceWin32HandleInfoKHR where
withCStruct :: forall b.
ExportFenceWin32HandleInfoKHR
-> (Ptr ExportFenceWin32HandleInfoKHR -> IO b) -> IO b
withCStruct ExportFenceWin32HandleInfoKHR
x Ptr ExportFenceWin32HandleInfoKHR -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \Ptr ExportFenceWin32HandleInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExportFenceWin32HandleInfoKHR
p ExportFenceWin32HandleInfoKHR
x (Ptr ExportFenceWin32HandleInfoKHR -> IO b
f Ptr ExportFenceWin32HandleInfoKHR
p)
pokeCStruct :: forall b.
Ptr ExportFenceWin32HandleInfoKHR
-> ExportFenceWin32HandleInfoKHR -> IO b -> IO b
pokeCStruct Ptr ExportFenceWin32HandleInfoKHR
p ExportFenceWin32HandleInfoKHR{DWORD
LPCWSTR
Ptr SECURITY_ATTRIBUTES
name :: LPCWSTR
dwAccess :: DWORD
attributes :: Ptr SECURITY_ATTRIBUTES
$sel:name:ExportFenceWin32HandleInfoKHR :: ExportFenceWin32HandleInfoKHR -> LPCWSTR
$sel:dwAccess:ExportFenceWin32HandleInfoKHR :: ExportFenceWin32HandleInfoKHR -> DWORD
$sel:attributes:ExportFenceWin32HandleInfoKHR :: ExportFenceWin32HandleInfoKHR -> Ptr SECURITY_ATTRIBUTES
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_FENCE_WIN32_HANDLE_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportFenceWin32HandleInfoKHR
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 ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr SECURITY_ATTRIBUTES))) (Ptr SECURITY_ATTRIBUTES
attributes)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DWORD)) (DWORD
dwAccess)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr LPCWSTR)) (LPCWSTR
name)
IO b
f
cStructSize :: Int
cStructSize = Int
40
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr ExportFenceWin32HandleInfoKHR -> IO b -> IO b
pokeZeroCStruct Ptr ExportFenceWin32HandleInfoKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_FENCE_WIN32_HANDLE_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportFenceWin32HandleInfoKHR
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 ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DWORD)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr LPCWSTR)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct ExportFenceWin32HandleInfoKHR where
peekCStruct :: Ptr ExportFenceWin32HandleInfoKHR
-> IO ExportFenceWin32HandleInfoKHR
peekCStruct Ptr ExportFenceWin32HandleInfoKHR
p = do
Ptr SECURITY_ATTRIBUTES
pAttributes <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr SECURITY_ATTRIBUTES) ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr SECURITY_ATTRIBUTES)))
DWORD
dwAccess <- forall a. Storable a => Ptr a -> IO a
peek @DWORD ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DWORD))
LPCWSTR
name <- forall a. Storable a => Ptr a -> IO a
peek @LPCWSTR ((Ptr ExportFenceWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr LPCWSTR))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Ptr SECURITY_ATTRIBUTES
-> DWORD -> LPCWSTR -> ExportFenceWin32HandleInfoKHR
ExportFenceWin32HandleInfoKHR
Ptr SECURITY_ATTRIBUTES
pAttributes DWORD
dwAccess LPCWSTR
name
instance Storable ExportFenceWin32HandleInfoKHR where
sizeOf :: ExportFenceWin32HandleInfoKHR -> Int
sizeOf ~ExportFenceWin32HandleInfoKHR
_ = Int
40
alignment :: ExportFenceWin32HandleInfoKHR -> Int
alignment ~ExportFenceWin32HandleInfoKHR
_ = Int
8
peek :: Ptr ExportFenceWin32HandleInfoKHR
-> IO ExportFenceWin32HandleInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ExportFenceWin32HandleInfoKHR
-> ExportFenceWin32HandleInfoKHR -> IO ()
poke Ptr ExportFenceWin32HandleInfoKHR
ptr ExportFenceWin32HandleInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExportFenceWin32HandleInfoKHR
ptr ExportFenceWin32HandleInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ExportFenceWin32HandleInfoKHR where
zero :: ExportFenceWin32HandleInfoKHR
zero = Ptr SECURITY_ATTRIBUTES
-> DWORD -> LPCWSTR -> ExportFenceWin32HandleInfoKHR
ExportFenceWin32HandleInfoKHR
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data FenceGetWin32HandleInfoKHR = FenceGetWin32HandleInfoKHR
{
FenceGetWin32HandleInfoKHR -> Fence
fence :: Fence
,
FenceGetWin32HandleInfoKHR -> ExternalFenceHandleTypeFlagBits
handleType :: ExternalFenceHandleTypeFlagBits
}
deriving (Typeable, FenceGetWin32HandleInfoKHR -> FenceGetWin32HandleInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FenceGetWin32HandleInfoKHR -> FenceGetWin32HandleInfoKHR -> Bool
$c/= :: FenceGetWin32HandleInfoKHR -> FenceGetWin32HandleInfoKHR -> Bool
== :: FenceGetWin32HandleInfoKHR -> FenceGetWin32HandleInfoKHR -> Bool
$c== :: FenceGetWin32HandleInfoKHR -> FenceGetWin32HandleInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (FenceGetWin32HandleInfoKHR)
#endif
deriving instance Show FenceGetWin32HandleInfoKHR
instance ToCStruct FenceGetWin32HandleInfoKHR where
withCStruct :: forall b.
FenceGetWin32HandleInfoKHR
-> (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> IO b)
-> IO b
withCStruct FenceGetWin32HandleInfoKHR
x ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p FenceGetWin32HandleInfoKHR
x (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR) -> IO b
f "pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p)
pokeCStruct :: forall b.
("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> FenceGetWin32HandleInfoKHR -> IO b -> IO b
pokeCStruct "pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p FenceGetWin32HandleInfoKHR{Fence
ExternalFenceHandleTypeFlagBits
handleType :: ExternalFenceHandleTypeFlagBits
fence :: Fence
$sel:handleType:FenceGetWin32HandleInfoKHR :: FenceGetWin32HandleInfoKHR -> ExternalFenceHandleTypeFlagBits
$sel:fence:FenceGetWin32HandleInfoKHR :: FenceGetWin32HandleInfoKHR -> Fence
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FENCE_GET_WIN32_HANDLE_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
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 (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Fence)) (Fence
fence)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalFenceHandleTypeFlagBits)) (ExternalFenceHandleTypeFlagBits
handleType)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> IO b -> IO b
pokeZeroCStruct "pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FENCE_GET_WIN32_HANDLE_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
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 (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Fence)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalFenceHandleTypeFlagBits)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct FenceGetWin32HandleInfoKHR where
peekCStruct :: ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> IO FenceGetWin32HandleInfoKHR
peekCStruct "pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p = do
Fence
fence <- forall a. Storable a => Ptr a -> IO a
peek @Fence (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Fence))
ExternalFenceHandleTypeFlagBits
handleType <- forall a. Storable a => Ptr a -> IO a
peek @ExternalFenceHandleTypeFlagBits (("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalFenceHandleTypeFlagBits))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Fence
-> ExternalFenceHandleTypeFlagBits -> FenceGetWin32HandleInfoKHR
FenceGetWin32HandleInfoKHR
Fence
fence ExternalFenceHandleTypeFlagBits
handleType
instance Storable FenceGetWin32HandleInfoKHR where
sizeOf :: FenceGetWin32HandleInfoKHR -> Int
sizeOf ~FenceGetWin32HandleInfoKHR
_ = Int
32
alignment :: FenceGetWin32HandleInfoKHR -> Int
alignment ~FenceGetWin32HandleInfoKHR
_ = Int
8
peek :: ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> IO FenceGetWin32HandleInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR)
-> FenceGetWin32HandleInfoKHR -> IO ()
poke "pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
ptr FenceGetWin32HandleInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pGetWin32HandleInfo" ::: Ptr FenceGetWin32HandleInfoKHR
ptr FenceGetWin32HandleInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero FenceGetWin32HandleInfoKHR where
zero :: FenceGetWin32HandleInfoKHR
zero = Fence
-> ExternalFenceHandleTypeFlagBits -> FenceGetWin32HandleInfoKHR
FenceGetWin32HandleInfoKHR
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type KHR_EXTERNAL_FENCE_WIN32_SPEC_VERSION = 1
pattern KHR_EXTERNAL_FENCE_WIN32_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_EXTERNAL_FENCE_WIN32_SPEC_VERSION :: forall a. Integral a => a
$mKHR_EXTERNAL_FENCE_WIN32_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_EXTERNAL_FENCE_WIN32_SPEC_VERSION = 1
type KHR_EXTERNAL_FENCE_WIN32_EXTENSION_NAME = "VK_KHR_external_fence_win32"
pattern KHR_EXTERNAL_FENCE_WIN32_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_EXTERNAL_FENCE_WIN32_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mKHR_EXTERNAL_FENCE_WIN32_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_EXTERNAL_FENCE_WIN32_EXTENSION_NAME = "VK_KHR_external_fence_win32"