{-# language CPP #-}
-- | = Name
--
-- VK_NV_external_memory_rdma - device extension
--
-- == VK_NV_external_memory_rdma
--
-- [__Name String__]
--     @VK_NV_external_memory_rdma@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     372
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_external_memory@ to be enabled for any
--         device-level functionality
--
-- [__Contact__]
--
--     -   Carsten Rohde
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_NV_external_memory_rdma] @crohde%0A*Here describe the issue or question you have about the VK_NV_external_memory_rdma extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2021-04-19
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Carsten Rohde, NVIDIA
--
-- == Description
--
-- This extension adds support for allocating memory which can be used for
-- remote direct memory access (RDMA) from other devices.
--
-- == New Base Types
--
-- -   'RemoteAddressNV'
--
-- == New Commands
--
-- -   'getMemoryRemoteAddressNV'
--
-- == New Structures
--
-- -   'MemoryGetRemoteAddressInfoNV'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceExternalMemoryRDMAFeaturesNV'
--
-- == New Enum Constants
--
-- -   'NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME'
--
-- -   'NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION'
--
-- -   Extending
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.ExternalMemoryHandleTypeFlagBits':
--
--     -   'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_RDMA_ADDRESS_BIT_NV'
--
-- -   Extending
--     'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MemoryPropertyFlagBits':
--
--     -   'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_GET_REMOTE_ADDRESS_INFO_NV'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_RDMA_FEATURES_NV'
--
-- == Examples
--
-- > VkPhysicalDeviceMemoryBudgetPropertiesEXT memoryBudgetProperties = { VK_STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_BUDGET_PROPERTIES_EXT };
-- > VkPhysicalDeviceMemoryProperties2 memoryProperties2 = { VK_STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PROPERTIES_2, &memoryBudgetProperties };
-- > vkGetPhysicalDeviceMemoryProperties2(physicalDevice, &memoryProperties2);
-- > uint32_t heapIndex = (uint32_t)-1;
-- > for (uint32_t memoryType = 0; memoryType < memoryProperties2.memoryProperties.memoryTypeCount; memoryType++) {
-- >     if (memoryProperties2.memoryProperties.memoryTypes[memoryType].propertyFlags & VK_MEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV) {
-- >         heapIndex = memoryProperties2.memoryProperties.memoryTypes[memoryType].heapIndex;
-- >         break;
-- >     }
-- > }
-- > if ((heapIndex == (uint32_t)-1) ||
-- >     (memoryBudgetProperties.heapBudget[heapIndex] < size)) {
-- >     return;
-- > }
-- >
-- > VkPhysicalDeviceExternalBufferInfo externalBufferInfo = { VK_STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_BUFFER_INFO };
-- > externalBufferInfo.usage = VK_BUFFER_USAGE_TRANSFER_SRC_BIT | VK_BUFFER_USAGE_TRANSFER_DST_BIT;
-- > externalBufferInfo.handleType = VK_EXTERNAL_MEMORY_HANDLE_TYPE_RDMA_ADDRESS_BIT_NV;
-- >
-- > VkExternalBufferProperties externalBufferProperties = { VK_STRUCTURE_TYPE_EXTERNAL_BUFFER_PROPERTIES };
-- > vkGetPhysicalDeviceExternalBufferProperties(physicalDevice, &externalBufferInfo, &externalBufferProperties);
-- >
-- > if (!(externalBufferProperties.externalMemoryProperties.externalMemoryFeatures & VK_EXTERNAL_MEMORY_FEATURE_EXPORTABLE_BIT)) {
-- >     return;
-- > }
-- >
-- > VkExternalMemoryBufferCreateInfo externalMemoryBufferCreateInfo = { VK_STRUCTURE_TYPE_EXTERNAL_MEMORY_BUFFER_CREATE_INFO };
-- > externalMemoryBufferCreateInfo.handleTypes = VK_EXTERNAL_MEMORY_HANDLE_TYPE_RDMA_ADDRESS_BIT_NV;
-- >
-- > VkBufferCreateInfo bufferCreateInfo = { VK_STRUCTURE_TYPE_BUFFER_CREATE_INFO, &externalMemoryBufferCreateInfo };
-- > bufferCreateInfo.size = size;
-- > bufferCreateInfo.usage = VK_BUFFER_USAGE_TRANSFER_SRC_BIT | VK_BUFFER_USAGE_TRANSFER_DST_BIT;
-- >
-- > VkMemoryRequirements mem_reqs;
-- > vkCreateBuffer(device, &bufferCreateInfo, NULL, &buffer);
-- > vkGetBufferMemoryRequirements(device, buffer, &mem_reqs);
-- >
-- > VkExportMemoryAllocateInfo exportMemoryAllocateInfo = { VK_STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO };
-- > exportMemoryAllocateInfo.handleTypes = VK_EXTERNAL_MEMORY_HANDLE_TYPE_RDMA_ADDRESS_BIT_NV;
-- >
-- > // Find memory type index
-- > uint32_t i = 0;
-- > for (; i < VK_MAX_MEMORY_TYPES; i++) {
-- >     if ((mem_reqs.memoryTypeBits & (1 << i)) &&
-- >         (memoryProperties.memoryTypes[i].propertyFlags & VK_MEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV)) {
-- >         break;
-- >     }
-- > }
-- >
-- > VkMemoryAllocateInfo memAllocInfo = { VK_STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO, &exportMemoryAllocateInfo };
-- > memAllocInfo.allocationSize = mem_reqs.size;
-- > memAllocInfo.memoryTypeIndex = i;
-- >
-- > vkAllocateMemory(device, &memAllocInfo, NULL, &mem);
-- > vkBindBufferMemory(device, buffer, mem, 0);
-- >
-- > VkMemoryGetRemoteAddressInfoNV getMemoryRemoteAddressInfo = { VK_STRUCTURE_TYPE_MEMORY_GET_REMOTE_ADDRESS_INFO_NV };
-- > getMemoryRemoteAddressInfo.memory = mem;
-- > getMemoryRemoteAddressInfo.handleType = VK_EXTERNAL_MEMORY_HANDLE_TYPE_RDMA_ADDRESS_BIT_NV;
-- >
-- > VkRemoteAddressNV rdmaAddress;
-- > vkGetMemoryRemoteAddressNV(device, &getMemoryRemoteAddressInfo, &rdmaAddress);
-- > // address returned in 'rdmaAddress' can be used by external devices to initiate RDMA transfers
--
-- == Version History
--
-- -   Revision 1, 2020-12-15 (Carsten Rohde)
--
--     -   Internal revisions
--
-- == See Also
--
-- 'MemoryGetRemoteAddressInfoNV',
-- 'PhysicalDeviceExternalMemoryRDMAFeaturesNV', 'RemoteAddressNV',
-- 'getMemoryRemoteAddressNV'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_NV_external_memory_rdma Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
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

-- | vkGetMemoryRemoteAddressNV - Get an address for a memory object
-- accessible by remote devices
--
-- = Description
--
-- More communication may be required between the kernel-mode drivers of
-- the devices involved. This information is out of scope of this
-- documentation and should be requested from the vendors of the devices.
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_INVALID_EXTERNAL_HANDLE'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_external_memory_rdma VK_NV_external_memory_rdma>,
-- 'Vulkan.Core10.Handles.Device', 'MemoryGetRemoteAddressInfoNV',
-- 'RemoteAddressNV'
getMemoryRemoteAddressNV :: forall io
                          . (MonadIO io)
                         => -- | @device@ is the logical device that created the device memory being
                            -- exported.
                            --
                            -- #VUID-vkGetMemoryRemoteAddressNV-device-parameter# @device@ /must/ be a
                            -- valid 'Vulkan.Core10.Handles.Device' handle
                            Device
                         -> -- | @pMemoryGetRemoteAddressInfo@ is a pointer to a
                            -- 'MemoryGetRemoteAddressInfoNV' structure containing parameters of the
                            -- export operation.
                            --
                            -- #VUID-vkGetMemoryRemoteAddressNV-pMemoryGetRemoteAddressInfo-parameter#
                            -- @pMemoryGetRemoteAddressInfo@ /must/ be a valid pointer to a valid
                            -- 'MemoryGetRemoteAddressInfoNV' structure
                            MemoryGetRemoteAddressInfoNV
                         -> io (RemoteAddressNV)
getMemoryRemoteAddressNV :: forall (io :: * -> *).
MonadIO io =>
Device -> MemoryGetRemoteAddressInfoNV -> io RemoteAddressNV
getMemoryRemoteAddressNV Device
device
                           MemoryGetRemoteAddressInfoNV
memoryGetRemoteAddressInfo = 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 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)
  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
   -> ("pMemoryGetRemoteAddressInfo"
       ::: Ptr MemoryGetRemoteAddressInfoNV)
   -> ("pAddress" ::: Ptr RemoteAddressNV)
   -> IO Result)
vkGetMemoryRemoteAddressNVPtr 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 vkGetMemoryRemoteAddressNV is null" forall a. Maybe a
Nothing 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 <- 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 (MemoryGetRemoteAddressInfoNV
memoryGetRemoteAddressInfo)
  "pAddress" ::: Ptr RemoteAddressNV
pPAddress <- 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 @RemoteAddressNV 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
"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))
  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))
  RemoteAddressNV
pAddress <- 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 @RemoteAddressNV "pAddress" ::: Ptr RemoteAddressNV
pPAddress
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (RemoteAddressNV
pAddress)


-- | VkPhysicalDeviceExternalMemoryRDMAFeaturesNV - Structure describing the
-- external memory RDMA features supported by the implementation
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceExternalMemoryRDMAFeaturesNV' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceExternalMemoryRDMAFeaturesNV' /can/ also be
-- used in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_external_memory_rdma VK_NV_external_memory_rdma>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceExternalMemoryRDMAFeaturesNV = PhysicalDeviceExternalMemoryRDMAFeaturesNV
  { -- | #features-externalMemoryRDMA# @externalMemoryRDMA@ indicates whether the
    -- implementation has support for the
    -- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV'
    -- memory property and the
    -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_RDMA_ADDRESS_BIT_NV'
    -- external memory handle type.
    PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
externalMemoryRDMA :: Bool }
  deriving (Typeable, PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
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 :: forall b.
PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> (Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b) -> IO b
withCStruct PhysicalDeviceExternalMemoryRDMAFeaturesNV
x Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p -> 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 :: forall b.
Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p PhysicalDeviceExternalMemoryRDMAFeaturesNV{Bool
externalMemoryRDMA :: Bool
$sel:externalMemoryRDMA:PhysicalDeviceExternalMemoryRDMAFeaturesNV :: PhysicalDeviceExternalMemoryRDMAFeaturesNV -> Bool
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_RDMA_FEATURES_NV)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
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 PhysicalDeviceExternalMemoryRDMAFeaturesNV
p 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 :: forall b.
Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_RDMA_FEATURES_NV)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
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 PhysicalDeviceExternalMemoryRDMAFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (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 <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure 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 = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
-> PhysicalDeviceExternalMemoryRDMAFeaturesNV -> IO ()
poke Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
ptr PhysicalDeviceExternalMemoryRDMAFeaturesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceExternalMemoryRDMAFeaturesNV where
  zero :: PhysicalDeviceExternalMemoryRDMAFeaturesNV
zero = Bool -> PhysicalDeviceExternalMemoryRDMAFeaturesNV
PhysicalDeviceExternalMemoryRDMAFeaturesNV
           forall a. Zero a => a
zero


-- | VkMemoryGetRemoteAddressInfoNV - Structure describing a remote
-- accessible address export operation
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_external_memory_rdma VK_NV_external_memory_rdma>,
-- 'Vulkan.Core10.Handles.DeviceMemory',
-- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.ExternalMemoryHandleTypeFlagBits',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getMemoryRemoteAddressNV'
data MemoryGetRemoteAddressInfoNV = MemoryGetRemoteAddressInfoNV
  { -- | @memory@ is the memory object from which the remote accessible address
    -- will be exported.
    --
    -- #VUID-VkMemoryGetRemoteAddressInfoNV-memory-parameter# @memory@ /must/
    -- be a valid 'Vulkan.Core10.Handles.DeviceMemory' handle
    MemoryGetRemoteAddressInfoNV -> DeviceMemory
memory :: DeviceMemory
  , -- | @handleType@ is the type of handle requested.
    --
    -- #VUID-VkMemoryGetRemoteAddressInfoNV-handleType-04966# @handleType@
    -- /must/ have been included in
    -- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExportMemoryAllocateInfo'::@handleTypes@
    -- when @memory@ was created
    --
    -- #VUID-VkMemoryGetRemoteAddressInfoNV-handleType-parameter# @handleType@
    -- /must/ be a valid
    -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.ExternalMemoryHandleTypeFlagBits'
    -- value
    MemoryGetRemoteAddressInfoNV -> ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
  }
  deriving (Typeable, MemoryGetRemoteAddressInfoNV
-> MemoryGetRemoteAddressInfoNV -> Bool
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 :: forall b.
MemoryGetRemoteAddressInfoNV
-> (("pMemoryGetRemoteAddressInfo"
     ::: Ptr MemoryGetRemoteAddressInfoNV)
    -> IO b)
-> IO b
withCStruct MemoryGetRemoteAddressInfoNV
x ("pMemoryGetRemoteAddressInfo"
 ::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p -> 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 :: forall b.
("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
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_REMOTE_ADDRESS_INFO_NV)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
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 (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
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 (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
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.
("pMemoryGetRemoteAddressInfo"
 ::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO b -> IO b
pokeZeroCStruct "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_REMOTE_ADDRESS_INFO_NV)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
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 (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
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 (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
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 MemoryGetRemoteAddressInfoNV where
  peekCStruct :: ("pMemoryGetRemoteAddressInfo"
 ::: Ptr MemoryGetRemoteAddressInfoNV)
-> IO MemoryGetRemoteAddressInfoNV
peekCStruct "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
p = do
    DeviceMemory
memory <- forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
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 (("pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
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 -> 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 = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pMemoryGetRemoteAddressInfo"
 ::: Ptr MemoryGetRemoteAddressInfoNV)
-> MemoryGetRemoteAddressInfoNV -> IO ()
poke "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
ptr MemoryGetRemoteAddressInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryGetRemoteAddressInfo" ::: Ptr MemoryGetRemoteAddressInfoNV
ptr MemoryGetRemoteAddressInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero MemoryGetRemoteAddressInfoNV where
  zero :: MemoryGetRemoteAddressInfoNV
zero = DeviceMemory
-> ExternalMemoryHandleTypeFlagBits -> MemoryGetRemoteAddressInfoNV
MemoryGetRemoteAddressInfoNV
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


type NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION"
pattern NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION :: forall a. Integral a => a
$mNV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_EXTERNAL_MEMORY_RDMA_SPEC_VERSION = 1


type NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME = "VK_NV_external_memory_rdma"

-- No documentation found for TopLevel "VK_NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME"
pattern NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_EXTERNAL_MEMORY_RDMA_EXTENSION_NAME = "VK_NV_external_memory_rdma"


-- | VkRemoteAddressNV - Remote device address type
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_external_memory_rdma VK_NV_external_memory_rdma>,
-- 'getMemoryRemoteAddressNV'
type RemoteAddressNV = Ptr ()