{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_external_memory_fd ( getMemoryFdKHR
, getMemoryFdPropertiesKHR
, ImportMemoryFdInfoKHR(..)
, MemoryFdPropertiesKHR(..)
, MemoryGetFdInfoKHR(..)
, KHR_EXTERNAL_MEMORY_FD_SPEC_VERSION
, pattern KHR_EXTERNAL_MEMORY_FD_SPEC_VERSION
, KHR_EXTERNAL_MEMORY_FD_EXTENSION_NAME
, pattern KHR_EXTERNAL_MEMORY_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.Word (Word32)
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(pVkGetMemoryFdKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetMemoryFdPropertiesKHR))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits (ExternalMemoryHandleTypeFlagBits)
import Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits (ExternalMemoryHandleTypeFlagBits(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMPORT_MEMORY_FD_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_FD_PROPERTIES_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_GET_FD_INFO_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetMemoryFdKHR
:: FunPtr (Ptr Device_T -> Ptr MemoryGetFdInfoKHR -> Ptr CInt -> IO Result) -> Ptr Device_T -> Ptr MemoryGetFdInfoKHR -> Ptr CInt -> IO Result
getMemoryFdKHR :: forall io
. (MonadIO io)
=>
Device
->
MemoryGetFdInfoKHR
-> io (("fd" ::: Int32))
getMemoryFdKHR :: forall (io :: * -> *).
MonadIO io =>
Device -> MemoryGetFdInfoKHR -> io ("fd" ::: Int32)
getMemoryFdKHR Device
device MemoryGetFdInfoKHR
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 vkGetMemoryFdKHRPtr :: FunPtr
(Ptr Device_T
-> ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
vkGetMemoryFdKHRPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
pVkGetMemoryFdKHR (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 MemoryGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
vkGetMemoryFdKHRPtr 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 vkGetMemoryFdKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetMemoryFdKHR' :: Ptr Device_T
-> ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result
vkGetMemoryFdKHR' = FunPtr
(Ptr Device_T
-> ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
-> Ptr Device_T
-> ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result
mkVkGetMemoryFdKHR FunPtr
(Ptr Device_T
-> ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result)
vkGetMemoryFdKHRPtr
"pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
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 (MemoryGetFdInfoKHR
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
"vkGetMemoryFdKHR" (Ptr Device_T
-> ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR)
-> ("pFd" ::: Ptr CInt)
-> IO Result
vkGetMemoryFdKHR'
(Device -> Ptr Device_T
deviceHandle (Device
device))
"pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
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" mkVkGetMemoryFdPropertiesKHR
:: FunPtr (Ptr Device_T -> ExternalMemoryHandleTypeFlagBits -> CInt -> Ptr MemoryFdPropertiesKHR -> IO Result) -> Ptr Device_T -> ExternalMemoryHandleTypeFlagBits -> CInt -> Ptr MemoryFdPropertiesKHR -> IO Result
getMemoryFdPropertiesKHR :: forall io
. (MonadIO io)
=>
Device
->
ExternalMemoryHandleTypeFlagBits
->
("fd" ::: Int32)
-> io (MemoryFdPropertiesKHR)
getMemoryFdPropertiesKHR :: forall (io :: * -> *).
MonadIO io =>
Device
-> ExternalMemoryHandleTypeFlagBits
-> ("fd" ::: Int32)
-> io MemoryFdPropertiesKHR
getMemoryFdPropertiesKHR Device
device ExternalMemoryHandleTypeFlagBits
handleType "fd" ::: Int32
fd = 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 vkGetMemoryFdPropertiesKHRPtr :: FunPtr
(Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> CInt
-> ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO Result)
vkGetMemoryFdPropertiesKHRPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> CInt
-> ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO Result)
pVkGetMemoryFdPropertiesKHR (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
-> ExternalMemoryHandleTypeFlagBits
-> CInt
-> ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO Result)
vkGetMemoryFdPropertiesKHRPtr 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 vkGetMemoryFdPropertiesKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetMemoryFdPropertiesKHR' :: Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> CInt
-> ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO Result
vkGetMemoryFdPropertiesKHR' = FunPtr
(Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> CInt
-> ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO Result)
-> Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> CInt
-> ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO Result
mkVkGetMemoryFdPropertiesKHR FunPtr
(Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> CInt
-> ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO Result)
vkGetMemoryFdPropertiesKHRPtr
"pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
pPMemoryFdProperties <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @MemoryFdPropertiesKHR)
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
"vkGetMemoryFdPropertiesKHR" (Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> CInt
-> ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO Result
vkGetMemoryFdPropertiesKHR'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(ExternalMemoryHandleTypeFlagBits
handleType)
(("fd" ::: Int32) -> CInt
CInt ("fd" ::: Int32
fd))
("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
pPMemoryFdProperties))
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))
MemoryFdPropertiesKHR
pMemoryFdProperties <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @MemoryFdPropertiesKHR "pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
pPMemoryFdProperties
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (MemoryFdPropertiesKHR
pMemoryFdProperties)
data ImportMemoryFdInfoKHR = ImportMemoryFdInfoKHR
{
ImportMemoryFdInfoKHR -> ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
,
ImportMemoryFdInfoKHR -> "fd" ::: Int32
fd :: Int32
}
deriving (Typeable, ImportMemoryFdInfoKHR -> ImportMemoryFdInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportMemoryFdInfoKHR -> ImportMemoryFdInfoKHR -> Bool
$c/= :: ImportMemoryFdInfoKHR -> ImportMemoryFdInfoKHR -> Bool
== :: ImportMemoryFdInfoKHR -> ImportMemoryFdInfoKHR -> Bool
$c== :: ImportMemoryFdInfoKHR -> ImportMemoryFdInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImportMemoryFdInfoKHR)
#endif
deriving instance Show ImportMemoryFdInfoKHR
instance ToCStruct ImportMemoryFdInfoKHR where
withCStruct :: forall b.
ImportMemoryFdInfoKHR
-> (Ptr ImportMemoryFdInfoKHR -> IO b) -> IO b
withCStruct ImportMemoryFdInfoKHR
x Ptr ImportMemoryFdInfoKHR -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ImportMemoryFdInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImportMemoryFdInfoKHR
p ImportMemoryFdInfoKHR
x (Ptr ImportMemoryFdInfoKHR -> IO b
f Ptr ImportMemoryFdInfoKHR
p)
pokeCStruct :: forall b.
Ptr ImportMemoryFdInfoKHR -> ImportMemoryFdInfoKHR -> IO b -> IO b
pokeCStruct Ptr ImportMemoryFdInfoKHR
p ImportMemoryFdInfoKHR{"fd" ::: Int32
ExternalMemoryHandleTypeFlagBits
fd :: "fd" ::: Int32
handleType :: ExternalMemoryHandleTypeFlagBits
$sel:fd:ImportMemoryFdInfoKHR :: ImportMemoryFdInfoKHR -> "fd" ::: Int32
$sel:handleType:ImportMemoryFdInfoKHR :: ImportMemoryFdInfoKHR -> ExternalMemoryHandleTypeFlagBits
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_MEMORY_FD_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryFdInfoKHR
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 ImportMemoryFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ExternalMemoryHandleTypeFlagBits)) (ExternalMemoryHandleTypeFlagBits
handleType)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr CInt)) (("fd" ::: Int32) -> CInt
CInt ("fd" ::: Int32
fd))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr ImportMemoryFdInfoKHR -> IO b -> IO b
pokeZeroCStruct Ptr ImportMemoryFdInfoKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_MEMORY_FD_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryFdInfoKHR
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 ImportMemoryFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr CInt)) (("fd" ::: Int32) -> CInt
CInt (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct ImportMemoryFdInfoKHR where
peekCStruct :: Ptr ImportMemoryFdInfoKHR -> IO ImportMemoryFdInfoKHR
peekCStruct Ptr ImportMemoryFdInfoKHR
p = do
ExternalMemoryHandleTypeFlagBits
handleType <- forall a. Storable a => Ptr a -> IO a
peek @ExternalMemoryHandleTypeFlagBits ((Ptr ImportMemoryFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ExternalMemoryHandleTypeFlagBits))
CInt
fd <- forall a. Storable a => Ptr a -> IO a
peek @CInt ((Ptr ImportMemoryFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr CInt))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ExternalMemoryHandleTypeFlagBits
-> ("fd" ::: Int32) -> ImportMemoryFdInfoKHR
ImportMemoryFdInfoKHR
ExternalMemoryHandleTypeFlagBits
handleType (coerce :: forall a b. Coercible a b => a -> b
coerce @CInt @Int32 CInt
fd)
instance Storable ImportMemoryFdInfoKHR where
sizeOf :: ImportMemoryFdInfoKHR -> Int
sizeOf ~ImportMemoryFdInfoKHR
_ = Int
24
alignment :: ImportMemoryFdInfoKHR -> Int
alignment ~ImportMemoryFdInfoKHR
_ = Int
8
peek :: Ptr ImportMemoryFdInfoKHR -> IO ImportMemoryFdInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ImportMemoryFdInfoKHR -> ImportMemoryFdInfoKHR -> IO ()
poke Ptr ImportMemoryFdInfoKHR
ptr ImportMemoryFdInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImportMemoryFdInfoKHR
ptr ImportMemoryFdInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImportMemoryFdInfoKHR where
zero :: ImportMemoryFdInfoKHR
zero = ExternalMemoryHandleTypeFlagBits
-> ("fd" ::: Int32) -> ImportMemoryFdInfoKHR
ImportMemoryFdInfoKHR
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data MemoryFdPropertiesKHR = MemoryFdPropertiesKHR
{
MemoryFdPropertiesKHR -> Word32
memoryTypeBits :: Word32 }
deriving (Typeable, MemoryFdPropertiesKHR -> MemoryFdPropertiesKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryFdPropertiesKHR -> MemoryFdPropertiesKHR -> Bool
$c/= :: MemoryFdPropertiesKHR -> MemoryFdPropertiesKHR -> Bool
== :: MemoryFdPropertiesKHR -> MemoryFdPropertiesKHR -> Bool
$c== :: MemoryFdPropertiesKHR -> MemoryFdPropertiesKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryFdPropertiesKHR)
#endif
deriving instance Show MemoryFdPropertiesKHR
instance ToCStruct MemoryFdPropertiesKHR where
withCStruct :: forall b.
MemoryFdPropertiesKHR
-> (("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR) -> IO b)
-> IO b
withCStruct MemoryFdPropertiesKHR
x ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p MemoryFdPropertiesKHR
x (("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR) -> IO b
f "pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p)
pokeCStruct :: forall b.
("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> MemoryFdPropertiesKHR -> IO b -> IO b
pokeCStruct "pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p MemoryFdPropertiesKHR{Word32
memoryTypeBits :: Word32
$sel:memoryTypeBits:MemoryFdPropertiesKHR :: MemoryFdPropertiesKHR -> Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_FD_PROPERTIES_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
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 (("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
memoryTypeBits)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO b -> IO b
pokeZeroCStruct "pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_FD_PROPERTIES_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
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 (("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct MemoryFdPropertiesKHR where
peekCStruct :: ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO MemoryFdPropertiesKHR
peekCStruct "pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p = do
Word32
memoryTypeBits <- forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word32 -> MemoryFdPropertiesKHR
MemoryFdPropertiesKHR
Word32
memoryTypeBits
instance Storable MemoryFdPropertiesKHR where
sizeOf :: MemoryFdPropertiesKHR -> Int
sizeOf ~MemoryFdPropertiesKHR
_ = Int
24
alignment :: MemoryFdPropertiesKHR -> Int
alignment ~MemoryFdPropertiesKHR
_ = Int
8
peek :: ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> IO MemoryFdPropertiesKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR)
-> MemoryFdPropertiesKHR -> IO ()
poke "pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
ptr MemoryFdPropertiesKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryFdProperties" ::: Ptr MemoryFdPropertiesKHR
ptr MemoryFdPropertiesKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryFdPropertiesKHR where
zero :: MemoryFdPropertiesKHR
zero = Word32 -> MemoryFdPropertiesKHR
MemoryFdPropertiesKHR
forall a. Zero a => a
zero
data MemoryGetFdInfoKHR = MemoryGetFdInfoKHR
{
MemoryGetFdInfoKHR -> DeviceMemory
memory :: DeviceMemory
,
MemoryGetFdInfoKHR -> ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
}
deriving (Typeable, MemoryGetFdInfoKHR -> MemoryGetFdInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryGetFdInfoKHR -> MemoryGetFdInfoKHR -> Bool
$c/= :: MemoryGetFdInfoKHR -> MemoryGetFdInfoKHR -> Bool
== :: MemoryGetFdInfoKHR -> MemoryGetFdInfoKHR -> Bool
$c== :: MemoryGetFdInfoKHR -> MemoryGetFdInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryGetFdInfoKHR)
#endif
deriving instance Show MemoryGetFdInfoKHR
instance ToCStruct MemoryGetFdInfoKHR where
withCStruct :: forall b.
MemoryGetFdInfoKHR
-> (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR) -> IO b) -> IO b
withCStruct MemoryGetFdInfoKHR
x ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR) -> 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 MemoryGetFdInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p MemoryGetFdInfoKHR
x (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR) -> IO b
f "pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p)
pokeCStruct :: forall b.
("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR)
-> MemoryGetFdInfoKHR -> IO b -> IO b
pokeCStruct "pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p MemoryGetFdInfoKHR{DeviceMemory
ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
memory :: DeviceMemory
$sel:handleType:MemoryGetFdInfoKHR :: MemoryGetFdInfoKHR -> ExternalMemoryHandleTypeFlagBits
$sel:memory:MemoryGetFdInfoKHR :: MemoryGetFdInfoKHR -> DeviceMemory
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_FD_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
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 MemoryGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory)) (DeviceMemory
memory)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalMemoryHandleTypeFlagBits)) (ExternalMemoryHandleTypeFlagBits
handleType)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR) -> IO b -> IO b
pokeZeroCStruct "pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_FD_INFO_KHR)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
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 MemoryGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalMemoryHandleTypeFlagBits)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct MemoryGetFdInfoKHR where
peekCStruct :: ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR) -> IO MemoryGetFdInfoKHR
peekCStruct "pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p = do
DeviceMemory
memory <- forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory))
ExternalMemoryHandleTypeFlagBits
handleType <- forall a. Storable a => Ptr a -> IO a
peek @ExternalMemoryHandleTypeFlagBits (("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalMemoryHandleTypeFlagBits))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DeviceMemory
-> ExternalMemoryHandleTypeFlagBits -> MemoryGetFdInfoKHR
MemoryGetFdInfoKHR
DeviceMemory
memory ExternalMemoryHandleTypeFlagBits
handleType
instance Storable MemoryGetFdInfoKHR where
sizeOf :: MemoryGetFdInfoKHR -> Int
sizeOf ~MemoryGetFdInfoKHR
_ = Int
32
alignment :: MemoryGetFdInfoKHR -> Int
alignment ~MemoryGetFdInfoKHR
_ = Int
8
peek :: ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR) -> IO MemoryGetFdInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR)
-> MemoryGetFdInfoKHR -> IO ()
poke "pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
ptr MemoryGetFdInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pGetFdInfo" ::: Ptr MemoryGetFdInfoKHR
ptr MemoryGetFdInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryGetFdInfoKHR where
zero :: MemoryGetFdInfoKHR
zero = DeviceMemory
-> ExternalMemoryHandleTypeFlagBits -> MemoryGetFdInfoKHR
MemoryGetFdInfoKHR
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type KHR_EXTERNAL_MEMORY_FD_SPEC_VERSION = 1
pattern KHR_EXTERNAL_MEMORY_FD_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_EXTERNAL_MEMORY_FD_SPEC_VERSION :: forall a. Integral a => a
$mKHR_EXTERNAL_MEMORY_FD_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_EXTERNAL_MEMORY_FD_SPEC_VERSION = 1
type KHR_EXTERNAL_MEMORY_FD_EXTENSION_NAME = "VK_KHR_external_memory_fd"
pattern KHR_EXTERNAL_MEMORY_FD_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_EXTERNAL_MEMORY_FD_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mKHR_EXTERNAL_MEMORY_FD_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_EXTERNAL_MEMORY_FD_EXTENSION_NAME = "VK_KHR_external_memory_fd"