{-# language CPP #-}
module Vulkan.Extensions.VK_NV_external_memory_rdma ( getMemoryRemoteAddressNV
, PhysicalDeviceExternalMemoryRDMAFeaturesNV(..)
, MemoryGetRemoteAddressInfoNV(..)
, NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION
, pattern NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION
, NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME
, pattern NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME
, RemoteAddressNV
) 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.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetMemoryRemoteAddressNV))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.Handles (Device_T)
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_MEMORY_GET_REMOTE_ADDRESS_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_RDMA_FEATURES_NV))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetMemoryRemoteAddressNV
:: FunPtr (Ptr Device_T -> Ptr MemoryGetRemoteAddressInfoNV -> Ptr RemoteAddressNV -> IO Result) -> Ptr Device_T -> Ptr MemoryGetRemoteAddressInfoNV -> Ptr RemoteAddressNV -> IO Result
getMemoryRemoteAddressNV :: forall io
. (MonadIO io)
=>
Device
->
MemoryGetRemoteAddressInfoNV
-> io (RemoteAddressNV)
getMemoryRemoteAddressNV :: Device -> MemoryGetRemoteAddressInfoNV -> io RemoteAddressNV
getMemoryRemoteAddressNV Device
device MemoryGetRemoteAddressInfoNV
memoryGetRemoteAddressInfo = IO RemoteAddressNV -> io RemoteAddressNV
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO RemoteAddressNV -> io RemoteAddressNV)
-> (ContT RemoteAddressNV IO RemoteAddressNV -> IO RemoteAddressNV)
-> ContT RemoteAddressNV IO RemoteAddressNV
-> io RemoteAddressNV
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT RemoteAddressNV IO RemoteAddressNV -> IO RemoteAddressNV
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT RemoteAddressNV IO RemoteAddressNV -> io RemoteAddressNV)
-> ContT RemoteAddressNV IO RemoteAddressNV -> io RemoteAddressNV
forall a b. (a -> b) -> a -> b
$ do
let vkGetMemoryRemoteAddressNVPtr :: FunPtr
(Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result)
vkGetMemoryRemoteAddressNVPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result)
pVkGetMemoryRemoteAddressNV (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
IO () -> ContT RemoteAddressNV IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT RemoteAddressNV IO ())
-> IO () -> ContT RemoteAddressNV IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result)
vkGetMemoryRemoteAddressNVPtr FunPtr
(Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetMemoryRemoteAddressNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetMemoryRemoteAddressNV' :: Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result
vkGetMemoryRemoteAddressNV' = FunPtr
(Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result)
-> Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result
mkVkGetMemoryRemoteAddressNV FunPtr
(Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result)
vkGetMemoryRemoteAddressNVPtr
"pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
pMemoryGetRemoteAddressInfo <- ((("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO RemoteAddressNV)
-> IO RemoteAddressNV)
-> ContT
RemoteAddressNV
IO
("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO RemoteAddressNV)
-> IO RemoteAddressNV)
-> ContT
RemoteAddressNV
IO
("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV))
-> ((("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO RemoteAddressNV)
-> IO RemoteAddressNV)
-> ContT
RemoteAddressNV
IO
("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
forall a b. (a -> b) -> a -> b
$ MemoryGetRemoteAddressInfoNV
-> (("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO RemoteAddressNV)
-> IO RemoteAddressNV
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MemoryGetRemoteAddressInfoNV
memoryGetRemoteAddressInfo)
"pAddress" ::: Ptr RemoteAddressNV
pPAddress <- ((("pAddress" ::: Ptr RemoteAddressNV) -> IO RemoteAddressNV)
-> IO RemoteAddressNV)
-> ContT RemoteAddressNV IO ("pAddress" ::: Ptr RemoteAddressNV)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAddress" ::: Ptr RemoteAddressNV) -> IO RemoteAddressNV)
-> IO RemoteAddressNV)
-> ContT RemoteAddressNV IO ("pAddress" ::: Ptr RemoteAddressNV))
-> ((("pAddress" ::: Ptr RemoteAddressNV) -> IO RemoteAddressNV)
-> IO RemoteAddressNV)
-> ContT RemoteAddressNV IO ("pAddress" ::: Ptr RemoteAddressNV)
forall a b. (a -> b) -> a -> b
$ IO ("pAddress" ::: Ptr RemoteAddressNV)
-> (("pAddress" ::: Ptr RemoteAddressNV) -> IO ())
-> (("pAddress" ::: Ptr RemoteAddressNV) -> IO RemoteAddressNV)
-> IO RemoteAddressNV
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pAddress" ::: Ptr RemoteAddressNV)
forall a. Int -> IO (Ptr a)
callocBytes @RemoteAddressNV Int
8) ("pAddress" ::: Ptr RemoteAddressNV) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT RemoteAddressNV IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT RemoteAddressNV IO Result)
-> IO Result -> ContT RemoteAddressNV IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetMemoryRemoteAddressNV" (Ptr Device_T
-> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> ("pAddress" ::: Ptr RemoteAddressNV)
-> IO Result
vkGetMemoryRemoteAddressNV' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
pMemoryGetRemoteAddressInfo ("pAddress" ::: Ptr RemoteAddressNV
pPAddress))
IO () -> ContT RemoteAddressNV IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT RemoteAddressNV IO ())
-> IO () -> ContT RemoteAddressNV IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
RemoteAddressNV
pAddress <- IO RemoteAddressNV -> ContT RemoteAddressNV IO RemoteAddressNV
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO RemoteAddressNV -> ContT RemoteAddressNV IO RemoteAddressNV)
-> IO RemoteAddressNV -> ContT RemoteAddressNV IO RemoteAddressNV
forall a b. (a -> b) -> a -> b
$ ("pAddress" ::: Ptr RemoteAddressNV) -> IO RemoteAddressNV
forall a. Storable a => Ptr a -> IO a
peek @RemoteAddressNV "pAddress" ::: Ptr RemoteAddressNV
pPAddress
RemoteAddressNV -> ContT RemoteAddressNV IO RemoteAddressNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RemoteAddressNV -> ContT RemoteAddressNV IO RemoteAddressNV)
-> RemoteAddressNV -> ContT RemoteAddressNV IO RemoteAddressNV
forall a b. (a -> b) -> a -> b
$ (RemoteAddressNV
pAddress)
data PhysicalDeviceExternalMemoryRDMAFeaturesNV = PhysicalDeviceExternalMemoryRDMAFeaturesNV
{
PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
externalMemoryRDMA :: Bool }
deriving (Typeable, PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
(PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool)
-> (PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool)
-> Eq PhysicalDeviceExternalMemoryRDMAFeaturesNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
$c/= :: PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
== :: PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
$c== :: PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceExternalMemoryRDMAFeaturesNV)
#endif
deriving instance Show PhysicalDeviceExternalMemoryRDMAFeaturesNV
instance ToCStruct PhysicalDeviceExternalMemoryRDMAFeaturesNV where
withCStruct :: PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> (Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b) -> IO b
withCStruct PhysicalDeviceExternalMemoryRDMAFeaturesNV
x Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b
f = Int
-> (Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b) -> IO b)
-> (Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p -> Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p PhysicalDeviceExternalMemoryRDMAFeaturesNV
x (Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b
f Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p)
pokeCStruct :: Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p PhysicalDeviceExternalMemoryRDMAFeaturesNV{Bool
externalMemoryRDMA :: Bool
$sel:externalMemoryRDMA:PhysicalDeviceExternalMemoryRDMAFeaturesNV :: PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_RDMA_FEATURES_NV)
("pAddress" ::: Ptr RemoteAddressNV) -> RemoteAddressNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> Int -> "pAddress" ::: Ptr RemoteAddressNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (RemoteAddressNV
forall a. Ptr a
nullPtr)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
externalMemoryRDMA))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_RDMA_FEATURES_NV)
("pAddress" ::: Ptr RemoteAddressNV) -> RemoteAddressNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> Int -> "pAddress" ::: Ptr RemoteAddressNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (RemoteAddressNV
forall a. Ptr a
nullPtr)
Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PhysicalDeviceExternalMemoryRDMAFeaturesNV where
peekCStruct :: Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> IO PhysicalDeviceExternalMemoryRDMAFeaturesNV
peekCStruct Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p = do
Bool32
externalMemoryRDMA <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> IO PhysicalDeviceExternalMemoryRDMAFeaturesNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> IO PhysicalDeviceExternalMemoryRDMAFeaturesNV)
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> IO PhysicalDeviceExternalMemoryRDMAFeaturesNV
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceExternalMemoryRDMAFeaturesNV
PhysicalDeviceExternalMemoryRDMAFeaturesNV
(Bool32 -> Bool
bool32ToBool Bool32
externalMemoryRDMA)
instance Storable PhysicalDeviceExternalMemoryRDMAFeaturesNV where
sizeOf :: PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Int
sizeOf ~PhysicalDeviceExternalMemoryRDMAFeaturesNV
_ = Int
24
alignment :: PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Int
alignment ~PhysicalDeviceExternalMemoryRDMAFeaturesNV
_ = Int
8
peek :: Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> IO PhysicalDeviceExternalMemoryRDMAFeaturesNV
peek = Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> IO PhysicalDeviceExternalMemoryRDMAFeaturesNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO ()
poke Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
poked = Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PhysicalDeviceExternalMemoryRDMAFeaturesNV where
zero :: PhysicalDeviceExternalMemoryRDMAFeaturesNV
zero = Bool -> PhysicalDeviceExternalMemoryRDMAFeaturesNV
PhysicalDeviceExternalMemoryRDMAFeaturesNV
Bool
forall a. Zero a => a
zero
data MemoryGetRemoteAddressInfoNV = MemoryGetRemoteAddressInfoNV
{
MemoryGetRemoteAddressInfoNV -> DeviceMemory
memory :: DeviceMemory
,
MemoryGetRemoteAddressInfoNV -> ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
}
deriving (Typeable, MemoryGetRemoteAddressInfoNV
-> MemoryGetRemoteAddressInfoNV -> Bool
(MemoryGetRemoteAddressInfoNV
-> MemoryGetRemoteAddressInfoNV -> Bool)
-> (MemoryGetRemoteAddressInfoNV
-> MemoryGetRemoteAddressInfoNV -> Bool)
-> Eq MemoryGetRemoteAddressInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryGetRemoteAddressInfoNV
-> MemoryGetRemoteAddressInfoNV -> Bool
$c/= :: MemoryGetRemoteAddressInfoNV
-> MemoryGetRemoteAddressInfoNV -> Bool
== :: MemoryGetRemoteAddressInfoNV
-> MemoryGetRemoteAddressInfoNV -> Bool
$c== :: MemoryGetRemoteAddressInfoNV
-> MemoryGetRemoteAddressInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryGetRemoteAddressInfoNV)
#endif
deriving instance Show MemoryGetRemoteAddressInfoNV
instance ToCStruct MemoryGetRemoteAddressInfoNV where
withCStruct :: MemoryGetRemoteAddressInfoNV
-> (("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO b)
-> IO b
withCStruct MemoryGetRemoteAddressInfoNV
x ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO b
f = Int
-> (("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO b)
-> IO b)
-> (("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \"pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p -> ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> MemoryGetRemoteAddressInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p MemoryGetRemoteAddressInfoNV
x (("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO b
f "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p)
pokeCStruct :: ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> MemoryGetRemoteAddressInfoNV -> IO b -> IO b
pokeCStruct "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p MemoryGetRemoteAddressInfoNV{DeviceMemory
ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
memory :: DeviceMemory
$sel:handleType:MemoryGetRemoteAddressInfoNV :: MemoryGetRemoteAddressInfoNV -> ExternalMemoryHandleTypeFlagBits
$sel:memory:MemoryGetRemoteAddressInfoNV :: MemoryGetRemoteAddressInfoNV -> DeviceMemory
..} IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_REMOTE_ADDRESS_INFO_NV)
("pAddress" ::: Ptr RemoteAddressNV) -> RemoteAddressNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> "pAddress" ::: Ptr RemoteAddressNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (RemoteAddressNV
forall a. Ptr a
nullPtr)
Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory)) (DeviceMemory
memory)
Ptr ExternalMemoryHandleTypeFlagBits
-> ExternalMemoryHandleTypeFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> Ptr ExternalMemoryHandleTypeFlagBits
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 :: ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO b -> IO b
pokeZeroCStruct "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_REMOTE_ADDRESS_INFO_NV)
("pAddress" ::: Ptr RemoteAddressNV) -> RemoteAddressNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> "pAddress" ::: Ptr RemoteAddressNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (RemoteAddressNV
forall a. Ptr a
nullPtr)
Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory)) (DeviceMemory
forall a. Zero a => a
zero)
Ptr ExternalMemoryHandleTypeFlagBits
-> ExternalMemoryHandleTypeFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> Ptr ExternalMemoryHandleTypeFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalMemoryHandleTypeFlagBits)) (ExternalMemoryHandleTypeFlagBits
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct MemoryGetRemoteAddressInfoNV where
peekCStruct :: ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO MemoryGetRemoteAddressInfoNV
peekCStruct "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p = do
DeviceMemory
memory <- Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemory))
ExternalMemoryHandleTypeFlagBits
handleType <- Ptr ExternalMemoryHandleTypeFlagBits
-> IO ExternalMemoryHandleTypeFlagBits
forall a. Storable a => Ptr a -> IO a
peek @ExternalMemoryHandleTypeFlagBits (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> Int -> Ptr ExternalMemoryHandleTypeFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr ExternalMemoryHandleTypeFlagBits))
MemoryGetRemoteAddressInfoNV -> IO MemoryGetRemoteAddressInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryGetRemoteAddressInfoNV -> IO MemoryGetRemoteAddressInfoNV)
-> MemoryGetRemoteAddressInfoNV -> IO MemoryGetRemoteAddressInfoNV
forall a b. (a -> b) -> a -> b
$ DeviceMemory
-> ExternalMemoryHandleTypeFlagBits -> MemoryGetRemoteAddressInfoNV
MemoryGetRemoteAddressInfoNV
DeviceMemory
memory ExternalMemoryHandleTypeFlagBits
handleType
instance Storable MemoryGetRemoteAddressInfoNV where
sizeOf :: MemoryGetRemoteAddressInfoNV -> Int
sizeOf ~MemoryGetRemoteAddressInfoNV
_ = Int
32
alignment :: MemoryGetRemoteAddressInfoNV -> Int
alignment ~MemoryGetRemoteAddressInfoNV
_ = Int
8
peek :: ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO MemoryGetRemoteAddressInfoNV
peek = ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO MemoryGetRemoteAddressInfoNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> MemoryGetRemoteAddressInfoNV -> IO ()
poke "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
ptr MemoryGetRemoteAddressInfoNV
poked = ("pMemoryGetRemoteAddressInfo"
::: Ptr MemoryGetRemoteAddressInfoNV)
-> MemoryGetRemoteAddressInfoNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
ptr MemoryGetRemoteAddressInfoNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryGetRemoteAddressInfoNV where
zero :: MemoryGetRemoteAddressInfoNV
zero = DeviceMemory
-> ExternalMemoryHandleTypeFlagBits -> MemoryGetRemoteAddressInfoNV
MemoryGetRemoteAddressInfoNV
DeviceMemory
forall a. Zero a => a
zero
ExternalMemoryHandleTypeFlagBits
forall a. Zero a => a
zero
type NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION = 1
pattern NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION :: a
$mNV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION = 1
type NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME = "VK_NV_external_memory_rdma"
pattern NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME :: a
$mNV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME = "VK_NV_external_memory_rdma"
type RemoteAddressNV = Ptr ()