{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_external_memory_win32  ( getMemoryWin32HandleKHR
                                                       , getMemoryWin32HandlePropertiesKHR
                                                       , ImportMemoryWin32HandleInfoKHR(..)
                                                       , ExportMemoryWin32HandleInfoKHR(..)
                                                       , MemoryWin32HandlePropertiesKHR(..)
                                                       , MemoryGetWin32HandleInfoKHR(..)
                                                       , KHR_EXTERNAL_MEMORY_WIN32_SPEC_VERSION
                                                       , pattern KHR_EXTERNAL_MEMORY_WIN32_SPEC_VERSION
                                                       , KHR_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME
                                                       , pattern KHR_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME
                                                       , LPCWSTR
                                                       , HANDLE
                                                       , DWORD
                                                       , SECURITY_ATTRIBUTES
                                                       ) where
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CWchar)
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.Extensions.VK_NV_external_memory_win32 (DWORD)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetMemoryWin32HandleKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetMemoryWin32HandlePropertiesKHR))
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.Extensions.VK_NV_external_memory_win32 (HANDLE)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Extensions.VK_NV_external_memory_win32 (SECURITY_ATTRIBUTES)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_GET_WIN32_HANDLE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_WIN32_HANDLE_PROPERTIES_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_NV_external_memory_win32 (DWORD)
import Vulkan.Extensions.VK_NV_external_memory_win32 (HANDLE)
import Vulkan.Extensions.VK_NV_external_memory_win32 (SECURITY_ATTRIBUTES)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetMemoryWin32HandleKHR
  :: FunPtr (Ptr Device_T -> Ptr MemoryGetWin32HandleInfoKHR -> Ptr HANDLE -> IO Result) -> Ptr Device_T -> Ptr MemoryGetWin32HandleInfoKHR -> Ptr HANDLE -> IO Result
getMemoryWin32HandleKHR :: forall io
                         . (MonadIO io)
                        => 
                           
                           
                           
                           
                           Device
                        -> 
                           
                           
                           
                           
                           
                           MemoryGetWin32HandleInfoKHR
                        -> io (HANDLE)
getMemoryWin32HandleKHR :: forall (io :: * -> *).
MonadIO io =>
Device -> MemoryGetWin32HandleInfoKHR -> io HANDLE
getMemoryWin32HandleKHR Device
device MemoryGetWin32HandleInfoKHR
getWin32HandleInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkGetMemoryWin32HandleKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
   -> ("pHandle" ::: Ptr HANDLE)
   -> IO Result)
vkGetMemoryWin32HandleKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
      -> ("pHandle" ::: Ptr HANDLE)
      -> IO Result)
pVkGetMemoryWin32HandleKHR (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
   -> ("pHandle" ::: Ptr HANDLE)
   -> IO Result)
vkGetMemoryWin32HandleKHRPtr 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 vkGetMemoryWin32HandleKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkGetMemoryWin32HandleKHR' :: Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result
vkGetMemoryWin32HandleKHR' = FunPtr
  (Ptr Device_T
   -> ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
   -> ("pHandle" ::: Ptr HANDLE)
   -> IO Result)
-> Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result
mkVkGetMemoryWin32HandleKHR FunPtr
  (Ptr Device_T
   -> ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
   -> ("pHandle" ::: Ptr HANDLE)
   -> IO Result)
vkGetMemoryWin32HandleKHRPtr
  "pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
pGetWin32HandleInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MemoryGetWin32HandleInfoKHR
getWin32HandleInfo)
  "pHandle" ::: Ptr HANDLE
pPHandle <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @HANDLE Int
8) forall a. Ptr a -> IO ()
free
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetMemoryWin32HandleKHR" (Ptr Device_T
-> ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
-> ("pHandle" ::: Ptr HANDLE)
-> IO Result
vkGetMemoryWin32HandleKHR'
                                                              (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                              "pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
pGetWin32HandleInfo
                                                              ("pHandle" ::: Ptr HANDLE
pPHandle))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  HANDLE
pHandle <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @HANDLE "pHandle" ::: Ptr HANDLE
pPHandle
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (HANDLE
pHandle)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetMemoryWin32HandlePropertiesKHR
  :: FunPtr (Ptr Device_T -> ExternalMemoryHandleTypeFlagBits -> HANDLE -> Ptr MemoryWin32HandlePropertiesKHR -> IO Result) -> Ptr Device_T -> ExternalMemoryHandleTypeFlagBits -> HANDLE -> Ptr MemoryWin32HandlePropertiesKHR -> IO Result
getMemoryWin32HandlePropertiesKHR :: forall io
                                   . (MonadIO io)
                                  => 
                                     
                                     
                                     
                                     Device
                                  -> 
                                     
                                     
                                     
                                     
                                     
                                     
                                     
                                     
                                     
                                     
                                     ExternalMemoryHandleTypeFlagBits
                                  -> 
                                     
                                     
                                     
                                     HANDLE
                                  -> io (MemoryWin32HandlePropertiesKHR)
getMemoryWin32HandlePropertiesKHR :: forall (io :: * -> *).
MonadIO io =>
Device
-> ExternalMemoryHandleTypeFlagBits
-> HANDLE
-> io MemoryWin32HandlePropertiesKHR
getMemoryWin32HandlePropertiesKHR Device
device
                                    ExternalMemoryHandleTypeFlagBits
handleType
                                    HANDLE
handle = 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 vkGetMemoryWin32HandlePropertiesKHRPtr :: FunPtr
  (Ptr Device_T
   -> ExternalMemoryHandleTypeFlagBits
   -> HANDLE
   -> ("pMemoryWin32HandleProperties"
       ::: Ptr MemoryWin32HandlePropertiesKHR)
   -> IO Result)
vkGetMemoryWin32HandlePropertiesKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ExternalMemoryHandleTypeFlagBits
      -> HANDLE
      -> ("pMemoryWin32HandleProperties"
          ::: Ptr MemoryWin32HandlePropertiesKHR)
      -> IO Result)
pVkGetMemoryWin32HandlePropertiesKHR (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
   -> HANDLE
   -> ("pMemoryWin32HandleProperties"
       ::: Ptr MemoryWin32HandlePropertiesKHR)
   -> IO Result)
vkGetMemoryWin32HandlePropertiesKHRPtr 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 vkGetMemoryWin32HandlePropertiesKHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkGetMemoryWin32HandlePropertiesKHR' :: Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> HANDLE
-> ("pMemoryWin32HandleProperties"
    ::: Ptr MemoryWin32HandlePropertiesKHR)
-> IO Result
vkGetMemoryWin32HandlePropertiesKHR' = FunPtr
  (Ptr Device_T
   -> ExternalMemoryHandleTypeFlagBits
   -> HANDLE
   -> ("pMemoryWin32HandleProperties"
       ::: Ptr MemoryWin32HandlePropertiesKHR)
   -> IO Result)
-> Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> HANDLE
-> ("pMemoryWin32HandleProperties"
    ::: Ptr MemoryWin32HandlePropertiesKHR)
-> IO Result
mkVkGetMemoryWin32HandlePropertiesKHR FunPtr
  (Ptr Device_T
   -> ExternalMemoryHandleTypeFlagBits
   -> HANDLE
   -> ("pMemoryWin32HandleProperties"
       ::: Ptr MemoryWin32HandlePropertiesKHR)
   -> IO Result)
vkGetMemoryWin32HandlePropertiesKHRPtr
  "pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
pPMemoryWin32HandleProperties <- 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 @MemoryWin32HandlePropertiesKHR)
  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
"vkGetMemoryWin32HandlePropertiesKHR" (Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> HANDLE
-> ("pMemoryWin32HandleProperties"
    ::: Ptr MemoryWin32HandlePropertiesKHR)
-> IO Result
vkGetMemoryWin32HandlePropertiesKHR'
                                                                        (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                        (ExternalMemoryHandleTypeFlagBits
handleType)
                                                                        (HANDLE
handle)
                                                                        ("pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
pPMemoryWin32HandleProperties))
  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))
  MemoryWin32HandlePropertiesKHR
pMemoryWin32HandleProperties <- 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 @MemoryWin32HandlePropertiesKHR "pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
pPMemoryWin32HandleProperties
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (MemoryWin32HandlePropertiesKHR
pMemoryWin32HandleProperties)
data ImportMemoryWin32HandleInfoKHR = ImportMemoryWin32HandleInfoKHR
  { 
    
    
    ImportMemoryWin32HandleInfoKHR -> ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
  , 
    ImportMemoryWin32HandleInfoKHR -> HANDLE
handle :: HANDLE
  , 
    
    ImportMemoryWin32HandleInfoKHR -> LPCWSTR
name :: LPCWSTR
  }
  deriving (Typeable, ImportMemoryWin32HandleInfoKHR
-> ImportMemoryWin32HandleInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportMemoryWin32HandleInfoKHR
-> ImportMemoryWin32HandleInfoKHR -> Bool
$c/= :: ImportMemoryWin32HandleInfoKHR
-> ImportMemoryWin32HandleInfoKHR -> Bool
== :: ImportMemoryWin32HandleInfoKHR
-> ImportMemoryWin32HandleInfoKHR -> Bool
$c== :: ImportMemoryWin32HandleInfoKHR
-> ImportMemoryWin32HandleInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImportMemoryWin32HandleInfoKHR)
#endif
deriving instance Show ImportMemoryWin32HandleInfoKHR
instance ToCStruct ImportMemoryWin32HandleInfoKHR where
  withCStruct :: forall b.
ImportMemoryWin32HandleInfoKHR
-> (Ptr ImportMemoryWin32HandleInfoKHR -> IO b) -> IO b
withCStruct ImportMemoryWin32HandleInfoKHR
x Ptr ImportMemoryWin32HandleInfoKHR -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \Ptr ImportMemoryWin32HandleInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImportMemoryWin32HandleInfoKHR
p ImportMemoryWin32HandleInfoKHR
x (Ptr ImportMemoryWin32HandleInfoKHR -> IO b
f Ptr ImportMemoryWin32HandleInfoKHR
p)
  pokeCStruct :: forall b.
Ptr ImportMemoryWin32HandleInfoKHR
-> ImportMemoryWin32HandleInfoKHR -> IO b -> IO b
pokeCStruct Ptr ImportMemoryWin32HandleInfoKHR
p ImportMemoryWin32HandleInfoKHR{HANDLE
LPCWSTR
ExternalMemoryHandleTypeFlagBits
name :: LPCWSTR
handle :: HANDLE
handleType :: ExternalMemoryHandleTypeFlagBits
$sel:name:ImportMemoryWin32HandleInfoKHR :: ImportMemoryWin32HandleInfoKHR -> LPCWSTR
$sel:handle:ImportMemoryWin32HandleInfoKHR :: ImportMemoryWin32HandleInfoKHR -> HANDLE
$sel:handleType:ImportMemoryWin32HandleInfoKHR :: ImportMemoryWin32HandleInfoKHR -> ExternalMemoryHandleTypeFlagBits
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoKHR
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 ImportMemoryWin32HandleInfoKHR
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 ImportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr HANDLE)) (HANDLE
handle)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr LPCWSTR)) (LPCWSTR
name)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr ImportMemoryWin32HandleInfoKHR -> IO b -> IO b
pokeZeroCStruct Ptr ImportMemoryWin32HandleInfoKHR
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f
instance FromCStruct ImportMemoryWin32HandleInfoKHR where
  peekCStruct :: Ptr ImportMemoryWin32HandleInfoKHR
-> IO ImportMemoryWin32HandleInfoKHR
peekCStruct Ptr ImportMemoryWin32HandleInfoKHR
p = do
    ExternalMemoryHandleTypeFlagBits
handleType <- forall a. Storable a => Ptr a -> IO a
peek @ExternalMemoryHandleTypeFlagBits ((Ptr ImportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ExternalMemoryHandleTypeFlagBits))
    HANDLE
handle <- forall a. Storable a => Ptr a -> IO a
peek @HANDLE ((Ptr ImportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr HANDLE))
    LPCWSTR
name <- forall a. Storable a => Ptr a -> IO a
peek @LPCWSTR ((Ptr ImportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr LPCWSTR))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ExternalMemoryHandleTypeFlagBits
-> HANDLE -> LPCWSTR -> ImportMemoryWin32HandleInfoKHR
ImportMemoryWin32HandleInfoKHR
             ExternalMemoryHandleTypeFlagBits
handleType HANDLE
handle LPCWSTR
name
instance Storable ImportMemoryWin32HandleInfoKHR where
  sizeOf :: ImportMemoryWin32HandleInfoKHR -> Int
sizeOf ~ImportMemoryWin32HandleInfoKHR
_ = Int
40
  alignment :: ImportMemoryWin32HandleInfoKHR -> Int
alignment ~ImportMemoryWin32HandleInfoKHR
_ = Int
8
  peek :: Ptr ImportMemoryWin32HandleInfoKHR
-> IO ImportMemoryWin32HandleInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr ImportMemoryWin32HandleInfoKHR
-> ImportMemoryWin32HandleInfoKHR -> IO ()
poke Ptr ImportMemoryWin32HandleInfoKHR
ptr ImportMemoryWin32HandleInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImportMemoryWin32HandleInfoKHR
ptr ImportMemoryWin32HandleInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ImportMemoryWin32HandleInfoKHR where
  zero :: ImportMemoryWin32HandleInfoKHR
zero = ExternalMemoryHandleTypeFlagBits
-> HANDLE -> LPCWSTR -> ImportMemoryWin32HandleInfoKHR
ImportMemoryWin32HandleInfoKHR
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
data ExportMemoryWin32HandleInfoKHR = ExportMemoryWin32HandleInfoKHR
  { 
    
    
    ExportMemoryWin32HandleInfoKHR -> Ptr SECURITY_ATTRIBUTES
attributes :: Ptr SECURITY_ATTRIBUTES
  , 
    
    ExportMemoryWin32HandleInfoKHR -> DWORD
dwAccess :: DWORD
  , 
    
    ExportMemoryWin32HandleInfoKHR -> LPCWSTR
name :: LPCWSTR
  }
  deriving (Typeable, ExportMemoryWin32HandleInfoKHR
-> ExportMemoryWin32HandleInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportMemoryWin32HandleInfoKHR
-> ExportMemoryWin32HandleInfoKHR -> Bool
$c/= :: ExportMemoryWin32HandleInfoKHR
-> ExportMemoryWin32HandleInfoKHR -> Bool
== :: ExportMemoryWin32HandleInfoKHR
-> ExportMemoryWin32HandleInfoKHR -> Bool
$c== :: ExportMemoryWin32HandleInfoKHR
-> ExportMemoryWin32HandleInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ExportMemoryWin32HandleInfoKHR)
#endif
deriving instance Show ExportMemoryWin32HandleInfoKHR
instance ToCStruct ExportMemoryWin32HandleInfoKHR where
  withCStruct :: forall b.
ExportMemoryWin32HandleInfoKHR
-> (Ptr ExportMemoryWin32HandleInfoKHR -> IO b) -> IO b
withCStruct ExportMemoryWin32HandleInfoKHR
x Ptr ExportMemoryWin32HandleInfoKHR -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \Ptr ExportMemoryWin32HandleInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExportMemoryWin32HandleInfoKHR
p ExportMemoryWin32HandleInfoKHR
x (Ptr ExportMemoryWin32HandleInfoKHR -> IO b
f Ptr ExportMemoryWin32HandleInfoKHR
p)
  pokeCStruct :: forall b.
Ptr ExportMemoryWin32HandleInfoKHR
-> ExportMemoryWin32HandleInfoKHR -> IO b -> IO b
pokeCStruct Ptr ExportMemoryWin32HandleInfoKHR
p ExportMemoryWin32HandleInfoKHR{DWORD
LPCWSTR
Ptr SECURITY_ATTRIBUTES
name :: LPCWSTR
dwAccess :: DWORD
attributes :: Ptr SECURITY_ATTRIBUTES
$sel:name:ExportMemoryWin32HandleInfoKHR :: ExportMemoryWin32HandleInfoKHR -> LPCWSTR
$sel:dwAccess:ExportMemoryWin32HandleInfoKHR :: ExportMemoryWin32HandleInfoKHR -> DWORD
$sel:attributes:ExportMemoryWin32HandleInfoKHR :: ExportMemoryWin32HandleInfoKHR -> Ptr SECURITY_ATTRIBUTES
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoKHR
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 ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr SECURITY_ATTRIBUTES))) (Ptr SECURITY_ATTRIBUTES
attributes)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DWORD)) (DWORD
dwAccess)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr LPCWSTR)) (LPCWSTR
name)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr ExportMemoryWin32HandleInfoKHR -> IO b -> IO b
pokeZeroCStruct Ptr ExportMemoryWin32HandleInfoKHR
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoKHR
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 ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DWORD)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr LPCWSTR)) (forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct ExportMemoryWin32HandleInfoKHR where
  peekCStruct :: Ptr ExportMemoryWin32HandleInfoKHR
-> IO ExportMemoryWin32HandleInfoKHR
peekCStruct Ptr ExportMemoryWin32HandleInfoKHR
p = do
    Ptr SECURITY_ATTRIBUTES
pAttributes <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr SECURITY_ATTRIBUTES) ((Ptr ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr SECURITY_ATTRIBUTES)))
    DWORD
dwAccess <- forall a. Storable a => Ptr a -> IO a
peek @DWORD ((Ptr ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DWORD))
    LPCWSTR
name <- forall a. Storable a => Ptr a -> IO a
peek @LPCWSTR ((Ptr ExportMemoryWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr LPCWSTR))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Ptr SECURITY_ATTRIBUTES
-> DWORD -> LPCWSTR -> ExportMemoryWin32HandleInfoKHR
ExportMemoryWin32HandleInfoKHR
             Ptr SECURITY_ATTRIBUTES
pAttributes DWORD
dwAccess LPCWSTR
name
instance Storable ExportMemoryWin32HandleInfoKHR where
  sizeOf :: ExportMemoryWin32HandleInfoKHR -> Int
sizeOf ~ExportMemoryWin32HandleInfoKHR
_ = Int
40
  alignment :: ExportMemoryWin32HandleInfoKHR -> Int
alignment ~ExportMemoryWin32HandleInfoKHR
_ = Int
8
  peek :: Ptr ExportMemoryWin32HandleInfoKHR
-> IO ExportMemoryWin32HandleInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr ExportMemoryWin32HandleInfoKHR
-> ExportMemoryWin32HandleInfoKHR -> IO ()
poke Ptr ExportMemoryWin32HandleInfoKHR
ptr ExportMemoryWin32HandleInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExportMemoryWin32HandleInfoKHR
ptr ExportMemoryWin32HandleInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ExportMemoryWin32HandleInfoKHR where
  zero :: ExportMemoryWin32HandleInfoKHR
zero = Ptr SECURITY_ATTRIBUTES
-> DWORD -> LPCWSTR -> ExportMemoryWin32HandleInfoKHR
ExportMemoryWin32HandleInfoKHR
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
data MemoryWin32HandlePropertiesKHR = MemoryWin32HandlePropertiesKHR
  { 
    
    MemoryWin32HandlePropertiesKHR -> DWORD
memoryTypeBits :: Word32 }
  deriving (Typeable, MemoryWin32HandlePropertiesKHR
-> MemoryWin32HandlePropertiesKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryWin32HandlePropertiesKHR
-> MemoryWin32HandlePropertiesKHR -> Bool
$c/= :: MemoryWin32HandlePropertiesKHR
-> MemoryWin32HandlePropertiesKHR -> Bool
== :: MemoryWin32HandlePropertiesKHR
-> MemoryWin32HandlePropertiesKHR -> Bool
$c== :: MemoryWin32HandlePropertiesKHR
-> MemoryWin32HandlePropertiesKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryWin32HandlePropertiesKHR)
#endif
deriving instance Show MemoryWin32HandlePropertiesKHR
instance ToCStruct MemoryWin32HandlePropertiesKHR where
  withCStruct :: forall b.
MemoryWin32HandlePropertiesKHR
-> (("pMemoryWin32HandleProperties"
     ::: Ptr MemoryWin32HandlePropertiesKHR)
    -> IO b)
-> IO b
withCStruct MemoryWin32HandlePropertiesKHR
x ("pMemoryWin32HandleProperties"
 ::: Ptr MemoryWin32HandlePropertiesKHR)
-> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
p MemoryWin32HandlePropertiesKHR
x (("pMemoryWin32HandleProperties"
 ::: Ptr MemoryWin32HandlePropertiesKHR)
-> IO b
f "pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
p)
  pokeCStruct :: forall b.
("pMemoryWin32HandleProperties"
 ::: Ptr MemoryWin32HandlePropertiesKHR)
-> MemoryWin32HandlePropertiesKHR -> IO b -> IO b
pokeCStruct "pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
p MemoryWin32HandlePropertiesKHR{DWORD
memoryTypeBits :: DWORD
$sel:memoryTypeBits:MemoryWin32HandlePropertiesKHR :: MemoryWin32HandlePropertiesKHR -> DWORD
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_WIN32_HANDLE_PROPERTIES_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
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 (("pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (DWORD
memoryTypeBits)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pMemoryWin32HandleProperties"
 ::: Ptr MemoryWin32HandlePropertiesKHR)
-> IO b -> IO b
pokeZeroCStruct "pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_WIN32_HANDLE_PROPERTIES_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
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 (("pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
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 MemoryWin32HandlePropertiesKHR where
  peekCStruct :: ("pMemoryWin32HandleProperties"
 ::: Ptr MemoryWin32HandlePropertiesKHR)
-> IO MemoryWin32HandlePropertiesKHR
peekCStruct "pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
p = do
    DWORD
memoryTypeBits <- forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
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
$ DWORD -> MemoryWin32HandlePropertiesKHR
MemoryWin32HandlePropertiesKHR
             DWORD
memoryTypeBits
instance Storable MemoryWin32HandlePropertiesKHR where
  sizeOf :: MemoryWin32HandlePropertiesKHR -> Int
sizeOf ~MemoryWin32HandlePropertiesKHR
_ = Int
24
  alignment :: MemoryWin32HandlePropertiesKHR -> Int
alignment ~MemoryWin32HandlePropertiesKHR
_ = Int
8
  peek :: ("pMemoryWin32HandleProperties"
 ::: Ptr MemoryWin32HandlePropertiesKHR)
-> IO MemoryWin32HandlePropertiesKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pMemoryWin32HandleProperties"
 ::: Ptr MemoryWin32HandlePropertiesKHR)
-> MemoryWin32HandlePropertiesKHR -> IO ()
poke "pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
ptr MemoryWin32HandlePropertiesKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryWin32HandleProperties"
::: Ptr MemoryWin32HandlePropertiesKHR
ptr MemoryWin32HandlePropertiesKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryWin32HandlePropertiesKHR where
  zero :: MemoryWin32HandlePropertiesKHR
zero = DWORD -> MemoryWin32HandlePropertiesKHR
MemoryWin32HandlePropertiesKHR
           forall a. Zero a => a
zero
data MemoryGetWin32HandleInfoKHR = MemoryGetWin32HandleInfoKHR
  { 
    MemoryGetWin32HandleInfoKHR -> DeviceMemory
memory :: DeviceMemory
  , 
    
    
    MemoryGetWin32HandleInfoKHR -> ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
  }
  deriving (Typeable, MemoryGetWin32HandleInfoKHR -> MemoryGetWin32HandleInfoKHR -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryGetWin32HandleInfoKHR -> MemoryGetWin32HandleInfoKHR -> Bool
$c/= :: MemoryGetWin32HandleInfoKHR -> MemoryGetWin32HandleInfoKHR -> Bool
== :: MemoryGetWin32HandleInfoKHR -> MemoryGetWin32HandleInfoKHR -> Bool
$c== :: MemoryGetWin32HandleInfoKHR -> MemoryGetWin32HandleInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryGetWin32HandleInfoKHR)
#endif
deriving instance Show MemoryGetWin32HandleInfoKHR
instance ToCStruct MemoryGetWin32HandleInfoKHR where
  withCStruct :: forall b.
MemoryGetWin32HandleInfoKHR
-> (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
    -> IO b)
-> IO b
withCStruct MemoryGetWin32HandleInfoKHR
x ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p MemoryGetWin32HandleInfoKHR
x (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR) -> IO b
f "pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p)
  pokeCStruct :: forall b.
("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
-> MemoryGetWin32HandleInfoKHR -> IO b -> IO b
pokeCStruct "pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p MemoryGetWin32HandleInfoKHR{DeviceMemory
ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
memory :: DeviceMemory
$sel:handleType:MemoryGetWin32HandleInfoKHR :: MemoryGetWin32HandleInfoKHR -> ExternalMemoryHandleTypeFlagBits
$sel:memory:MemoryGetWin32HandleInfoKHR :: MemoryGetWin32HandleInfoKHR -> DeviceMemory
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_WIN32_HANDLE_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
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 (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
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.
("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
-> IO b -> IO b
pokeZeroCStruct "pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_GET_WIN32_HANDLE_INFO_KHR)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
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 (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
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 MemoryGetWin32HandleInfoKHR where
  peekCStruct :: ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
-> IO MemoryGetWin32HandleInfoKHR
peekCStruct "pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
p = do
    DeviceMemory
memory <- forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
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 (("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
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 -> MemoryGetWin32HandleInfoKHR
MemoryGetWin32HandleInfoKHR
             DeviceMemory
memory ExternalMemoryHandleTypeFlagBits
handleType
instance Storable MemoryGetWin32HandleInfoKHR where
  sizeOf :: MemoryGetWin32HandleInfoKHR -> Int
sizeOf ~MemoryGetWin32HandleInfoKHR
_ = Int
32
  alignment :: MemoryGetWin32HandleInfoKHR -> Int
alignment ~MemoryGetWin32HandleInfoKHR
_ = Int
8
  peek :: ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
-> IO MemoryGetWin32HandleInfoKHR
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR)
-> MemoryGetWin32HandleInfoKHR -> IO ()
poke "pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
ptr MemoryGetWin32HandleInfoKHR
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pGetWin32HandleInfo" ::: Ptr MemoryGetWin32HandleInfoKHR
ptr MemoryGetWin32HandleInfoKHR
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MemoryGetWin32HandleInfoKHR where
  zero :: MemoryGetWin32HandleInfoKHR
zero = DeviceMemory
-> ExternalMemoryHandleTypeFlagBits -> MemoryGetWin32HandleInfoKHR
MemoryGetWin32HandleInfoKHR
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
type KHR_EXTERNAL_MEMORY_WIN32_SPEC_VERSION = 1
pattern KHR_EXTERNAL_MEMORY_WIN32_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_EXTERNAL_MEMORY_WIN32_SPEC_VERSION :: forall a. Integral a => a
$mKHR_EXTERNAL_MEMORY_WIN32_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_EXTERNAL_MEMORY_WIN32_SPEC_VERSION = 1
type KHR_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME = "VK_KHR_external_memory_win32"
pattern KHR_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mKHR_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_EXTERNAL_MEMORY_WIN32_EXTENSION_NAME = "VK_KHR_external_memory_win32"
type LPCWSTR = Ptr CWchar