{-# language CPP #-}
module Vulkan.Extensions.VK_NV_external_memory_win32  ( getMemoryWin32HandleNV
                                                      , ImportMemoryWin32HandleInfoNV(..)
                                                      , ExportMemoryWin32HandleInfoNV(..)
                                                      , NV_EXTERNAL_MEMORY_WIN32_SPEC_VERSION
                                                      , pattern NV_EXTERNAL_MEMORY_WIN32_SPEC_VERSION
                                                      , NV_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME
                                                      , pattern NV_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME
                                                      , HANDLE
                                                      , DWORD
                                                      , SECURITY_ATTRIBUTES
                                                      , ExternalMemoryHandleTypeFlagBitsNV(..)
                                                      , ExternalMemoryHandleTypeFlagsNV
                                                      ) where

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
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 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.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkGetMemoryWin32HandleNV))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.Handles (DeviceMemory(..))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Extensions.VK_NV_external_memory_capabilities (ExternalMemoryHandleTypeFlagBitsNV(..))
import Vulkan.Extensions.VK_NV_external_memory_capabilities (ExternalMemoryHandleTypeFlagsNV)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_NV))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_NV_external_memory_capabilities (ExternalMemoryHandleTypeFlagBitsNV(..))
import Vulkan.Extensions.VK_NV_external_memory_capabilities (ExternalMemoryHandleTypeFlagsNV)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetMemoryWin32HandleNV
  :: FunPtr (Ptr Device_T -> DeviceMemory -> ExternalMemoryHandleTypeFlagsNV -> Ptr HANDLE -> IO Result) -> Ptr Device_T -> DeviceMemory -> ExternalMemoryHandleTypeFlagsNV -> Ptr HANDLE -> IO Result

-- | vkGetMemoryWin32HandleNV - retrieve Win32 handle to a device memory
-- object
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.DeviceMemory',
-- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagsNV'
getMemoryWin32HandleNV :: forall io
                        . (MonadIO io)
                       => -- | @device@ is the logical device that owns the memory.
                          --
                          -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                          Device
                       -> -- | @memory@ is the 'Vulkan.Core10.Handles.DeviceMemory' object.
                          --
                          -- @memory@ /must/ be a valid 'Vulkan.Core10.Handles.DeviceMemory' handle
                          --
                          -- @memory@ /must/ have been created, allocated, or retrieved from @device@
                          DeviceMemory
                       -> -- | @handleType@ is a bitmask of
                          -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagBitsNV'
                          -- containing a single bit specifying the type of handle requested.
                          --
                          -- @handleType@ /must/ be a flag specified in
                          -- 'Vulkan.Extensions.VK_NV_external_memory.ExportMemoryAllocateInfoNV'::@handleTypes@
                          -- when allocating @memory@
                          --
                          -- @handleType@ /must/ be a valid combination of
                          -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagBitsNV'
                          -- values
                          --
                          -- @handleType@ /must/ not be @0@
                          ExternalMemoryHandleTypeFlagsNV
                       -> io (HANDLE)
getMemoryWin32HandleNV :: Device
-> DeviceMemory -> ExternalMemoryHandleTypeFlagsNV -> io HANDLE
getMemoryWin32HandleNV device :: Device
device memory :: DeviceMemory
memory handleType :: ExternalMemoryHandleTypeFlagsNV
handleType = IO HANDLE -> io HANDLE
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO HANDLE -> io HANDLE)
-> (ContT HANDLE IO HANDLE -> IO HANDLE)
-> ContT HANDLE IO HANDLE
-> io HANDLE
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT HANDLE IO HANDLE -> IO HANDLE
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT HANDLE IO HANDLE -> io HANDLE)
-> ContT HANDLE IO HANDLE -> io HANDLE
forall a b. (a -> b) -> a -> b
$ do
  let vkGetMemoryWin32HandleNVPtr :: FunPtr
  (Ptr Device_T
   -> DeviceMemory
   -> ExternalMemoryHandleTypeFlagsNV
   -> ("pHandle" ::: Ptr HANDLE)
   -> IO Result)
vkGetMemoryWin32HandleNVPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> DeviceMemory
      -> ExternalMemoryHandleTypeFlagsNV
      -> ("pHandle" ::: Ptr HANDLE)
      -> IO Result)
pVkGetMemoryWin32HandleNV (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT HANDLE IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT HANDLE IO ()) -> IO () -> ContT HANDLE IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DeviceMemory
   -> ExternalMemoryHandleTypeFlagsNV
   -> ("pHandle" ::: Ptr HANDLE)
   -> IO Result)
vkGetMemoryWin32HandleNVPtr FunPtr
  (Ptr Device_T
   -> DeviceMemory
   -> ExternalMemoryHandleTypeFlagsNV
   -> ("pHandle" ::: Ptr HANDLE)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> DeviceMemory
      -> ExternalMemoryHandleTypeFlagsNV
      -> ("pHandle" ::: Ptr HANDLE)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> DeviceMemory
   -> ExternalMemoryHandleTypeFlagsNV
   -> ("pHandle" ::: Ptr HANDLE)
   -> 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 "" "The function pointer for vkGetMemoryWin32HandleNV is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetMemoryWin32HandleNV' :: Ptr Device_T
-> DeviceMemory
-> ExternalMemoryHandleTypeFlagsNV
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result
vkGetMemoryWin32HandleNV' = FunPtr
  (Ptr Device_T
   -> DeviceMemory
   -> ExternalMemoryHandleTypeFlagsNV
   -> ("pHandle" ::: Ptr HANDLE)
   -> IO Result)
-> Ptr Device_T
-> DeviceMemory
-> ExternalMemoryHandleTypeFlagsNV
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result
mkVkGetMemoryWin32HandleNV FunPtr
  (Ptr Device_T
   -> DeviceMemory
   -> ExternalMemoryHandleTypeFlagsNV
   -> ("pHandle" ::: Ptr HANDLE)
   -> IO Result)
vkGetMemoryWin32HandleNVPtr
  "pHandle" ::: Ptr HANDLE
pPHandle <- ((("pHandle" ::: Ptr HANDLE) -> IO HANDLE) -> IO HANDLE)
-> ContT HANDLE IO ("pHandle" ::: Ptr HANDLE)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pHandle" ::: Ptr HANDLE) -> IO HANDLE) -> IO HANDLE)
 -> ContT HANDLE IO ("pHandle" ::: Ptr HANDLE))
-> ((("pHandle" ::: Ptr HANDLE) -> IO HANDLE) -> IO HANDLE)
-> ContT HANDLE IO ("pHandle" ::: Ptr HANDLE)
forall a b. (a -> b) -> a -> b
$ IO ("pHandle" ::: Ptr HANDLE)
-> (("pHandle" ::: Ptr HANDLE) -> IO ())
-> (("pHandle" ::: Ptr HANDLE) -> IO HANDLE)
-> IO HANDLE
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pHandle" ::: Ptr HANDLE)
forall a. Int -> IO (Ptr a)
callocBytes @HANDLE 8) ("pHandle" ::: Ptr HANDLE) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT HANDLE IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT HANDLE IO Result)
-> IO Result -> ContT HANDLE IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> DeviceMemory
-> ExternalMemoryHandleTypeFlagsNV
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result
vkGetMemoryWin32HandleNV' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DeviceMemory
memory) (ExternalMemoryHandleTypeFlagsNV
handleType) ("pHandle" ::: Ptr HANDLE
pPHandle)
  IO () -> ContT HANDLE IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT HANDLE IO ()) -> IO () -> ContT HANDLE 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))
  HANDLE
pHandle <- IO HANDLE -> ContT HANDLE IO HANDLE
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO HANDLE -> ContT HANDLE IO HANDLE)
-> IO HANDLE -> ContT HANDLE IO HANDLE
forall a b. (a -> b) -> a -> b
$ ("pHandle" ::: Ptr HANDLE) -> IO HANDLE
forall a. Storable a => Ptr a -> IO a
peek @HANDLE "pHandle" ::: Ptr HANDLE
pPHandle
  HANDLE -> ContT HANDLE IO HANDLE
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HANDLE -> ContT HANDLE IO HANDLE)
-> HANDLE -> ContT HANDLE IO HANDLE
forall a b. (a -> b) -> a -> b
$ (HANDLE
pHandle)


-- | VkImportMemoryWin32HandleInfoNV - import Win32 memory created on the
-- same physical device
--
-- = Description
--
-- If @handleType@ is @0@, this structure is ignored by consumers of the
-- 'Vulkan.Core10.Memory.MemoryAllocateInfo' structure it is chained from.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagsNV',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ImportMemoryWin32HandleInfoNV = ImportMemoryWin32HandleInfoNV
  { -- | @handleType@ is @0@ or a
    -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagBitsNV'
    -- value specifying the type of memory handle in @handle@.
    --
    -- @handleType@ /must/ not have more than one bit set
    --
    -- @handleType@ /must/ be a valid combination of
    -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagBitsNV'
    -- values
    ImportMemoryWin32HandleInfoNV -> ExternalMemoryHandleTypeFlagsNV
handleType :: ExternalMemoryHandleTypeFlagsNV
  , -- | @handle@ is a Windows 'HANDLE' referring to the memory.
    --
    -- @handle@ /must/ be a valid handle to memory, obtained as specified by
    -- @handleType@
    ImportMemoryWin32HandleInfoNV -> HANDLE
handle :: HANDLE
  }
  deriving (Typeable, ImportMemoryWin32HandleInfoNV
-> ImportMemoryWin32HandleInfoNV -> Bool
(ImportMemoryWin32HandleInfoNV
 -> ImportMemoryWin32HandleInfoNV -> Bool)
-> (ImportMemoryWin32HandleInfoNV
    -> ImportMemoryWin32HandleInfoNV -> Bool)
-> Eq ImportMemoryWin32HandleInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportMemoryWin32HandleInfoNV
-> ImportMemoryWin32HandleInfoNV -> Bool
$c/= :: ImportMemoryWin32HandleInfoNV
-> ImportMemoryWin32HandleInfoNV -> Bool
== :: ImportMemoryWin32HandleInfoNV
-> ImportMemoryWin32HandleInfoNV -> Bool
$c== :: ImportMemoryWin32HandleInfoNV
-> ImportMemoryWin32HandleInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImportMemoryWin32HandleInfoNV)
#endif
deriving instance Show ImportMemoryWin32HandleInfoNV

instance ToCStruct ImportMemoryWin32HandleInfoNV where
  withCStruct :: ImportMemoryWin32HandleInfoNV
-> (Ptr ImportMemoryWin32HandleInfoNV -> IO b) -> IO b
withCStruct x :: ImportMemoryWin32HandleInfoNV
x f :: Ptr ImportMemoryWin32HandleInfoNV -> IO b
f = Int -> Int -> (Ptr ImportMemoryWin32HandleInfoNV -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr ImportMemoryWin32HandleInfoNV -> IO b) -> IO b)
-> (Ptr ImportMemoryWin32HandleInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ImportMemoryWin32HandleInfoNV
p -> Ptr ImportMemoryWin32HandleInfoNV
-> ImportMemoryWin32HandleInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImportMemoryWin32HandleInfoNV
p ImportMemoryWin32HandleInfoNV
x (Ptr ImportMemoryWin32HandleInfoNV -> IO b
f Ptr ImportMemoryWin32HandleInfoNV
p)
  pokeCStruct :: Ptr ImportMemoryWin32HandleInfoNV
-> ImportMemoryWin32HandleInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr ImportMemoryWin32HandleInfoNV
p ImportMemoryWin32HandleInfoNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoNV
p Ptr ImportMemoryWin32HandleInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_NV)
    ("pHandle" ::: Ptr HANDLE) -> HANDLE -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoNV
p Ptr ImportMemoryWin32HandleInfoNV
-> Int -> "pHandle" ::: Ptr HANDLE
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (HANDLE
forall a. Ptr a
nullPtr)
    Ptr ExternalMemoryHandleTypeFlagsNV
-> ExternalMemoryHandleTypeFlagsNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoNV
p Ptr ImportMemoryWin32HandleInfoNV
-> Int -> Ptr ExternalMemoryHandleTypeFlagsNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ExternalMemoryHandleTypeFlagsNV)) (ExternalMemoryHandleTypeFlagsNV
handleType)
    ("pHandle" ::: Ptr HANDLE) -> HANDLE -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoNV
p Ptr ImportMemoryWin32HandleInfoNV
-> Int -> "pHandle" ::: Ptr HANDLE
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr HANDLE)) (HANDLE
handle)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr ImportMemoryWin32HandleInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr ImportMemoryWin32HandleInfoNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoNV
p Ptr ImportMemoryWin32HandleInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_NV)
    ("pHandle" ::: Ptr HANDLE) -> HANDLE -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoNV
p Ptr ImportMemoryWin32HandleInfoNV
-> Int -> "pHandle" ::: Ptr HANDLE
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (HANDLE
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct ImportMemoryWin32HandleInfoNV where
  peekCStruct :: Ptr ImportMemoryWin32HandleInfoNV
-> IO ImportMemoryWin32HandleInfoNV
peekCStruct p :: Ptr ImportMemoryWin32HandleInfoNV
p = do
    ExternalMemoryHandleTypeFlagsNV
handleType <- Ptr ExternalMemoryHandleTypeFlagsNV
-> IO ExternalMemoryHandleTypeFlagsNV
forall a. Storable a => Ptr a -> IO a
peek @ExternalMemoryHandleTypeFlagsNV ((Ptr ImportMemoryWin32HandleInfoNV
p Ptr ImportMemoryWin32HandleInfoNV
-> Int -> Ptr ExternalMemoryHandleTypeFlagsNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ExternalMemoryHandleTypeFlagsNV))
    HANDLE
handle <- ("pHandle" ::: Ptr HANDLE) -> IO HANDLE
forall a. Storable a => Ptr a -> IO a
peek @HANDLE ((Ptr ImportMemoryWin32HandleInfoNV
p Ptr ImportMemoryWin32HandleInfoNV
-> Int -> "pHandle" ::: Ptr HANDLE
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr HANDLE))
    ImportMemoryWin32HandleInfoNV -> IO ImportMemoryWin32HandleInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImportMemoryWin32HandleInfoNV -> IO ImportMemoryWin32HandleInfoNV)
-> ImportMemoryWin32HandleInfoNV
-> IO ImportMemoryWin32HandleInfoNV
forall a b. (a -> b) -> a -> b
$ ExternalMemoryHandleTypeFlagsNV
-> HANDLE -> ImportMemoryWin32HandleInfoNV
ImportMemoryWin32HandleInfoNV
             ExternalMemoryHandleTypeFlagsNV
handleType HANDLE
handle

instance Storable ImportMemoryWin32HandleInfoNV where
  sizeOf :: ImportMemoryWin32HandleInfoNV -> Int
sizeOf ~ImportMemoryWin32HandleInfoNV
_ = 32
  alignment :: ImportMemoryWin32HandleInfoNV -> Int
alignment ~ImportMemoryWin32HandleInfoNV
_ = 8
  peek :: Ptr ImportMemoryWin32HandleInfoNV
-> IO ImportMemoryWin32HandleInfoNV
peek = Ptr ImportMemoryWin32HandleInfoNV
-> IO ImportMemoryWin32HandleInfoNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr ImportMemoryWin32HandleInfoNV
-> ImportMemoryWin32HandleInfoNV -> IO ()
poke ptr :: Ptr ImportMemoryWin32HandleInfoNV
ptr poked :: ImportMemoryWin32HandleInfoNV
poked = Ptr ImportMemoryWin32HandleInfoNV
-> ImportMemoryWin32HandleInfoNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImportMemoryWin32HandleInfoNV
ptr ImportMemoryWin32HandleInfoNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero ImportMemoryWin32HandleInfoNV where
  zero :: ImportMemoryWin32HandleInfoNV
zero = ExternalMemoryHandleTypeFlagsNV
-> HANDLE -> ImportMemoryWin32HandleInfoNV
ImportMemoryWin32HandleInfoNV
           ExternalMemoryHandleTypeFlagsNV
forall a. Zero a => a
zero
           HANDLE
forall a. Zero a => a
zero


-- | VkExportMemoryWin32HandleInfoNV - specify security attributes and access
-- rights for Win32 memory handles
--
-- = Description
--
-- If this structure is not present, or if @pAttributes@ is set to @NULL@,
-- default security descriptor values will be used, and child processes
-- created by the application will not inherit the handle, as described in
-- the MSDN documentation for “Synchronization Object Security and Access
-- Rights”1. Further, if the structure is not present, the access rights
-- will be
--
-- @DXGI_SHARED_RESOURCE_READ@ | @DXGI_SHARED_RESOURCE_WRITE@
--
-- [1]
--     <https://docs.microsoft.com/en-us/windows/win32/sync/synchronization-object-security-and-access-rights>
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_NV'
--
-- -   If @pAttributes@ is not @NULL@, @pAttributes@ /must/ be a valid
--     pointer to a valid 'SECURITY_ATTRIBUTES' value
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ExportMemoryWin32HandleInfoNV = ExportMemoryWin32HandleInfoNV
  { -- | @pAttributes@ is a pointer to a Windows 'SECURITY_ATTRIBUTES' structure
    -- specifying security attributes of the handle.
    ExportMemoryWin32HandleInfoNV -> Ptr SECURITY_ATTRIBUTES
attributes :: Ptr SECURITY_ATTRIBUTES
  , -- | @dwAccess@ is a 'DWORD' specifying access rights of the handle.
    ExportMemoryWin32HandleInfoNV -> DWORD
dwAccess :: DWORD
  }
  deriving (Typeable, ExportMemoryWin32HandleInfoNV
-> ExportMemoryWin32HandleInfoNV -> Bool
(ExportMemoryWin32HandleInfoNV
 -> ExportMemoryWin32HandleInfoNV -> Bool)
-> (ExportMemoryWin32HandleInfoNV
    -> ExportMemoryWin32HandleInfoNV -> Bool)
-> Eq ExportMemoryWin32HandleInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportMemoryWin32HandleInfoNV
-> ExportMemoryWin32HandleInfoNV -> Bool
$c/= :: ExportMemoryWin32HandleInfoNV
-> ExportMemoryWin32HandleInfoNV -> Bool
== :: ExportMemoryWin32HandleInfoNV
-> ExportMemoryWin32HandleInfoNV -> Bool
$c== :: ExportMemoryWin32HandleInfoNV
-> ExportMemoryWin32HandleInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ExportMemoryWin32HandleInfoNV)
#endif
deriving instance Show ExportMemoryWin32HandleInfoNV

instance ToCStruct ExportMemoryWin32HandleInfoNV where
  withCStruct :: ExportMemoryWin32HandleInfoNV
-> (Ptr ExportMemoryWin32HandleInfoNV -> IO b) -> IO b
withCStruct x :: ExportMemoryWin32HandleInfoNV
x f :: Ptr ExportMemoryWin32HandleInfoNV -> IO b
f = Int -> Int -> (Ptr ExportMemoryWin32HandleInfoNV -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr ExportMemoryWin32HandleInfoNV -> IO b) -> IO b)
-> (Ptr ExportMemoryWin32HandleInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ExportMemoryWin32HandleInfoNV
p -> Ptr ExportMemoryWin32HandleInfoNV
-> ExportMemoryWin32HandleInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExportMemoryWin32HandleInfoNV
p ExportMemoryWin32HandleInfoNV
x (Ptr ExportMemoryWin32HandleInfoNV -> IO b
f Ptr ExportMemoryWin32HandleInfoNV
p)
  pokeCStruct :: Ptr ExportMemoryWin32HandleInfoNV
-> ExportMemoryWin32HandleInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr ExportMemoryWin32HandleInfoNV
p ExportMemoryWin32HandleInfoNV{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoNV
p Ptr ExportMemoryWin32HandleInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_NV)
    ("pHandle" ::: Ptr HANDLE) -> HANDLE -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoNV
p Ptr ExportMemoryWin32HandleInfoNV
-> Int -> "pHandle" ::: Ptr HANDLE
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (HANDLE
forall a. Ptr a
nullPtr)
    Ptr (Ptr SECURITY_ATTRIBUTES) -> Ptr SECURITY_ATTRIBUTES -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoNV
p Ptr ExportMemoryWin32HandleInfoNV
-> Int -> Ptr (Ptr SECURITY_ATTRIBUTES)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SECURITY_ATTRIBUTES))) (Ptr SECURITY_ATTRIBUTES
attributes)
    Ptr DWORD -> DWORD -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoNV
p Ptr ExportMemoryWin32HandleInfoNV -> Int -> Ptr DWORD
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DWORD)) (DWORD
dwAccess)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr ExportMemoryWin32HandleInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr ExportMemoryWin32HandleInfoNV
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoNV
p Ptr ExportMemoryWin32HandleInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_NV)
    ("pHandle" ::: Ptr HANDLE) -> HANDLE -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoNV
p Ptr ExportMemoryWin32HandleInfoNV
-> Int -> "pHandle" ::: Ptr HANDLE
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (HANDLE
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct ExportMemoryWin32HandleInfoNV where
  peekCStruct :: Ptr ExportMemoryWin32HandleInfoNV
-> IO ExportMemoryWin32HandleInfoNV
peekCStruct p :: Ptr ExportMemoryWin32HandleInfoNV
p = do
    Ptr SECURITY_ATTRIBUTES
pAttributes <- Ptr (Ptr SECURITY_ATTRIBUTES) -> IO (Ptr SECURITY_ATTRIBUTES)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr SECURITY_ATTRIBUTES) ((Ptr ExportMemoryWin32HandleInfoNV
p Ptr ExportMemoryWin32HandleInfoNV
-> Int -> Ptr (Ptr SECURITY_ATTRIBUTES)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr SECURITY_ATTRIBUTES)))
    DWORD
dwAccess <- Ptr DWORD -> IO DWORD
forall a. Storable a => Ptr a -> IO a
peek @DWORD ((Ptr ExportMemoryWin32HandleInfoNV
p Ptr ExportMemoryWin32HandleInfoNV -> Int -> Ptr DWORD
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DWORD))
    ExportMemoryWin32HandleInfoNV -> IO ExportMemoryWin32HandleInfoNV
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ExportMemoryWin32HandleInfoNV -> IO ExportMemoryWin32HandleInfoNV)
-> ExportMemoryWin32HandleInfoNV
-> IO ExportMemoryWin32HandleInfoNV
forall a b. (a -> b) -> a -> b
$ Ptr SECURITY_ATTRIBUTES -> DWORD -> ExportMemoryWin32HandleInfoNV
ExportMemoryWin32HandleInfoNV
             Ptr SECURITY_ATTRIBUTES
pAttributes DWORD
dwAccess

instance Storable ExportMemoryWin32HandleInfoNV where
  sizeOf :: ExportMemoryWin32HandleInfoNV -> Int
sizeOf ~ExportMemoryWin32HandleInfoNV
_ = 32
  alignment :: ExportMemoryWin32HandleInfoNV -> Int
alignment ~ExportMemoryWin32HandleInfoNV
_ = 8
  peek :: Ptr ExportMemoryWin32HandleInfoNV
-> IO ExportMemoryWin32HandleInfoNV
peek = Ptr ExportMemoryWin32HandleInfoNV
-> IO ExportMemoryWin32HandleInfoNV
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr ExportMemoryWin32HandleInfoNV
-> ExportMemoryWin32HandleInfoNV -> IO ()
poke ptr :: Ptr ExportMemoryWin32HandleInfoNV
ptr poked :: ExportMemoryWin32HandleInfoNV
poked = Ptr ExportMemoryWin32HandleInfoNV
-> ExportMemoryWin32HandleInfoNV -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExportMemoryWin32HandleInfoNV
ptr ExportMemoryWin32HandleInfoNV
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero ExportMemoryWin32HandleInfoNV where
  zero :: ExportMemoryWin32HandleInfoNV
zero = Ptr SECURITY_ATTRIBUTES -> DWORD -> ExportMemoryWin32HandleInfoNV
ExportMemoryWin32HandleInfoNV
           Ptr SECURITY_ATTRIBUTES
forall a. Zero a => a
zero
           DWORD
forall a. Zero a => a
zero


type NV_EXTERNAL_MEMORY_WIN32_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NV_EXTERNAL_MEMORY_WIN32_SPEC_VERSION"
pattern NV_EXTERNAL_MEMORY_WIN32_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_EXTERNAL_MEMORY_WIN32_SPEC_VERSION :: a
$mNV_EXTERNAL_MEMORY_WIN32_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
NV_EXTERNAL_MEMORY_WIN32_SPEC_VERSION = 1


type NV_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME = "VK_NV_external_memory_win32"

-- No documentation found for TopLevel "VK_NV_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME"
pattern NV_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME :: a
$mNV_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME = "VK_NV_external_memory_win32"


type HANDLE = Ptr ()


type DWORD = Word32


data SECURITY_ATTRIBUTES