{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_external_memory_host  ( getMemoryHostPointerPropertiesEXT
                                                      , ImportMemoryHostPointerInfoEXT(..)
                                                      , MemoryHostPointerPropertiesEXT(..)
                                                      , PhysicalDeviceExternalMemoryHostPropertiesEXT(..)
                                                      , EXT_EXTERNAL_MEMORY_HOST_SPEC_VERSION
                                                      , pattern EXT_EXTERNAL_MEMORY_HOST_SPEC_VERSION
                                                      , EXT_EXTERNAL_MEMORY_HOST_EXTENSION_NAME
                                                      , pattern EXT_EXTERNAL_MEMORY_HOST_EXTENSION_NAME
                                                      ) where

import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
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.NamedType ((:::))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkGetMemoryHostPointerPropertiesEXT))
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits (ExternalMemoryHandleTypeFlagBits)
import Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits (ExternalMemoryHandleTypeFlagBits(..))
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_IMPORT_MEMORY_HOST_POINTER_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_HOST_POINTER_PROPERTIES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_HOST_PROPERTIES_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetMemoryHostPointerPropertiesEXT
  :: FunPtr (Ptr Device_T -> ExternalMemoryHandleTypeFlagBits -> Ptr () -> Ptr MemoryHostPointerPropertiesEXT -> IO Result) -> Ptr Device_T -> ExternalMemoryHandleTypeFlagBits -> Ptr () -> Ptr MemoryHostPointerPropertiesEXT -> IO Result

-- | vkGetMemoryHostPointerPropertiesEXT - Get properties of external memory
-- host pointer
--
-- == Valid Usage
--
-- -   @handleType@ /must/ be
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_HOST_ALLOCATION_BIT_EXT'
--     or
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_HOST_MAPPED_FOREIGN_MEMORY_BIT_EXT'
--
-- -   @pHostPointer@ /must/ be a pointer aligned to an integer multiple of
--     'PhysicalDeviceExternalMemoryHostPropertiesEXT'::@minImportedHostPointerAlignment@
--
-- -   If @handleType@ is
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_HOST_ALLOCATION_BIT_EXT',
--     @pHostPointer@ /must/ be a pointer to host memory
--
-- -   If @handleType@ is
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_HOST_MAPPED_FOREIGN_MEMORY_BIT_EXT',
--     @pHostPointer@ /must/ be a pointer to host mapped foreign memory
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @handleType@ /must/ be a valid
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.ExternalMemoryHandleTypeFlagBits'
--     value
--
-- -   @pMemoryHostPointerProperties@ /must/ be a valid pointer to a
--     'MemoryHostPointerPropertiesEXT' structure
--
-- == 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_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_INVALID_EXTERNAL_HANDLE'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.ExternalMemoryHandleTypeFlagBits',
-- 'MemoryHostPointerPropertiesEXT'
getMemoryHostPointerPropertiesEXT :: forall io
                                   . (MonadIO io)
                                  => -- | @device@ is the logical device that will be importing @pHostPointer@.
                                     Device
                                  -> -- | @handleType@ is the type of the handle @pHostPointer@.
                                     ExternalMemoryHandleTypeFlagBits
                                  -> -- | @pHostPointer@ is the host pointer to import from.
                                     ("hostPointer" ::: Ptr ())
                                  -> io (MemoryHostPointerPropertiesEXT)
getMemoryHostPointerPropertiesEXT :: Device
-> ExternalMemoryHandleTypeFlagBits
-> ("hostPointer" ::: Ptr ())
-> io MemoryHostPointerPropertiesEXT
getMemoryHostPointerPropertiesEXT device :: Device
device handleType :: ExternalMemoryHandleTypeFlagBits
handleType hostPointer :: "hostPointer" ::: Ptr ()
hostPointer = IO MemoryHostPointerPropertiesEXT
-> io MemoryHostPointerPropertiesEXT
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MemoryHostPointerPropertiesEXT
 -> io MemoryHostPointerPropertiesEXT)
-> (ContT
      MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT
    -> IO MemoryHostPointerPropertiesEXT)
-> ContT
     MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT
-> io MemoryHostPointerPropertiesEXT
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT
-> IO MemoryHostPointerPropertiesEXT
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT
 -> io MemoryHostPointerPropertiesEXT)
-> ContT
     MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT
-> io MemoryHostPointerPropertiesEXT
forall a b. (a -> b) -> a -> b
$ do
  let vkGetMemoryHostPointerPropertiesEXTPtr :: FunPtr
  (Ptr Device_T
   -> ExternalMemoryHandleTypeFlagBits
   -> ("hostPointer" ::: Ptr ())
   -> ("pMemoryHostPointerProperties"
       ::: Ptr MemoryHostPointerPropertiesEXT)
   -> IO Result)
vkGetMemoryHostPointerPropertiesEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ExternalMemoryHandleTypeFlagBits
      -> ("hostPointer" ::: Ptr ())
      -> ("pMemoryHostPointerProperties"
          ::: Ptr MemoryHostPointerPropertiesEXT)
      -> IO Result)
pVkGetMemoryHostPointerPropertiesEXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT MemoryHostPointerPropertiesEXT IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT MemoryHostPointerPropertiesEXT IO ())
-> IO () -> ContT MemoryHostPointerPropertiesEXT IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ExternalMemoryHandleTypeFlagBits
   -> ("hostPointer" ::: Ptr ())
   -> ("pMemoryHostPointerProperties"
       ::: Ptr MemoryHostPointerPropertiesEXT)
   -> IO Result)
vkGetMemoryHostPointerPropertiesEXTPtr FunPtr
  (Ptr Device_T
   -> ExternalMemoryHandleTypeFlagBits
   -> ("hostPointer" ::: Ptr ())
   -> ("pMemoryHostPointerProperties"
       ::: Ptr MemoryHostPointerPropertiesEXT)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ExternalMemoryHandleTypeFlagBits
      -> ("hostPointer" ::: Ptr ())
      -> ("pMemoryHostPointerProperties"
          ::: Ptr MemoryHostPointerPropertiesEXT)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ExternalMemoryHandleTypeFlagBits
   -> ("hostPointer" ::: Ptr ())
   -> ("pMemoryHostPointerProperties"
       ::: Ptr MemoryHostPointerPropertiesEXT)
   -> 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 vkGetMemoryHostPointerPropertiesEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetMemoryHostPointerPropertiesEXT' :: Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> ("hostPointer" ::: Ptr ())
-> ("pMemoryHostPointerProperties"
    ::: Ptr MemoryHostPointerPropertiesEXT)
-> IO Result
vkGetMemoryHostPointerPropertiesEXT' = FunPtr
  (Ptr Device_T
   -> ExternalMemoryHandleTypeFlagBits
   -> ("hostPointer" ::: Ptr ())
   -> ("pMemoryHostPointerProperties"
       ::: Ptr MemoryHostPointerPropertiesEXT)
   -> IO Result)
-> Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> ("hostPointer" ::: Ptr ())
-> ("pMemoryHostPointerProperties"
    ::: Ptr MemoryHostPointerPropertiesEXT)
-> IO Result
mkVkGetMemoryHostPointerPropertiesEXT FunPtr
  (Ptr Device_T
   -> ExternalMemoryHandleTypeFlagBits
   -> ("hostPointer" ::: Ptr ())
   -> ("pMemoryHostPointerProperties"
       ::: Ptr MemoryHostPointerPropertiesEXT)
   -> IO Result)
vkGetMemoryHostPointerPropertiesEXTPtr
  "pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
pPMemoryHostPointerProperties <- ((("pMemoryHostPointerProperties"
   ::: Ptr MemoryHostPointerPropertiesEXT)
  -> IO MemoryHostPointerPropertiesEXT)
 -> IO MemoryHostPointerPropertiesEXT)
-> ContT
     MemoryHostPointerPropertiesEXT
     IO
     ("pMemoryHostPointerProperties"
      ::: Ptr MemoryHostPointerPropertiesEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct MemoryHostPointerPropertiesEXT =>
(("pMemoryHostPointerProperties"
  ::: Ptr MemoryHostPointerPropertiesEXT)
 -> IO b)
-> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @MemoryHostPointerPropertiesEXT)
  Result
r <- IO Result -> ContT MemoryHostPointerPropertiesEXT IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT MemoryHostPointerPropertiesEXT IO Result)
-> IO Result -> ContT MemoryHostPointerPropertiesEXT IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ExternalMemoryHandleTypeFlagBits
-> ("hostPointer" ::: Ptr ())
-> ("pMemoryHostPointerProperties"
    ::: Ptr MemoryHostPointerPropertiesEXT)
-> IO Result
vkGetMemoryHostPointerPropertiesEXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) (ExternalMemoryHandleTypeFlagBits
handleType) ("hostPointer" ::: Ptr ()
hostPointer) ("pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
pPMemoryHostPointerProperties)
  IO () -> ContT MemoryHostPointerPropertiesEXT IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT MemoryHostPointerPropertiesEXT IO ())
-> IO () -> ContT MemoryHostPointerPropertiesEXT 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))
  MemoryHostPointerPropertiesEXT
pMemoryHostPointerProperties <- IO MemoryHostPointerPropertiesEXT
-> ContT
     MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO MemoryHostPointerPropertiesEXT
 -> ContT
      MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT)
-> IO MemoryHostPointerPropertiesEXT
-> ContT
     MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT
forall a b. (a -> b) -> a -> b
$ ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> IO MemoryHostPointerPropertiesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @MemoryHostPointerPropertiesEXT "pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
pPMemoryHostPointerProperties
  MemoryHostPointerPropertiesEXT
-> ContT
     MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryHostPointerPropertiesEXT
 -> ContT
      MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT)
-> MemoryHostPointerPropertiesEXT
-> ContT
     MemoryHostPointerPropertiesEXT IO MemoryHostPointerPropertiesEXT
forall a b. (a -> b) -> a -> b
$ (MemoryHostPointerPropertiesEXT
pMemoryHostPointerProperties)


-- | VkImportMemoryHostPointerInfoEXT - import memory from a host pointer
--
-- = Description
--
-- Importing memory from a host pointer shares ownership of the memory
-- between the host and the Vulkan implementation. The application /can/
-- continue to access the memory through the host pointer but it is the
-- application’s responsibility to synchronize device and non-device access
-- to the payload as defined in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-device-hostaccess Host Access to Device Memory Objects>.
--
-- Applications /can/ import the same payload into multiple instances of
-- Vulkan and multiple times into a given Vulkan instance. However,
-- implementations /may/ fail to import the same payload multiple times
-- into a given physical device due to platform constraints.
--
-- Importing memory from a particular host pointer /may/ not be possible
-- due to additional platform-specific restrictions beyond the scope of
-- this specification in which case the implementation /must/ fail the
-- memory import operation with the error code
-- 'Vulkan.Extensions.VK_KHR_external_memory.ERROR_INVALID_EXTERNAL_HANDLE_KHR'.
--
-- Whether device memory objects imported from a host pointer hold a
-- reference to their payload is undefined. As such, the application /must/
-- ensure that the imported memory range remains valid and accessible for
-- the lifetime of the imported memory object.
--
-- == Valid Usage
--
-- -   If @handleType@ is not @0@, it /must/ be supported for import, as
--     reported in
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.ExternalMemoryProperties'
--
-- -   If @handleType@ is not @0@, it /must/ be
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_HOST_ALLOCATION_BIT_EXT'
--     or
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_HOST_MAPPED_FOREIGN_MEMORY_BIT_EXT'
--
-- -   @pHostPointer@ /must/ be a pointer aligned to an integer multiple of
--     'PhysicalDeviceExternalMemoryHostPropertiesEXT'::@minImportedHostPointerAlignment@
--
-- -   If @handleType@ is
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_HOST_ALLOCATION_BIT_EXT',
--     @pHostPointer@ /must/ be a pointer to @allocationSize@ number of
--     bytes of host memory, where @allocationSize@ is the member of the
--     'Vulkan.Core10.Memory.MemoryAllocateInfo' structure this structure
--     is chained to
--
-- -   If @handleType@ is
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_HOST_MAPPED_FOREIGN_MEMORY_BIT_EXT',
--     @pHostPointer@ /must/ be a pointer to @allocationSize@ number of
--     bytes of host mapped foreign memory, where @allocationSize@ is the
--     member of the 'Vulkan.Core10.Memory.MemoryAllocateInfo' structure
--     this structure is chained to
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_IMPORT_MEMORY_HOST_POINTER_INFO_EXT'
--
-- -   @handleType@ /must/ be a valid
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.ExternalMemoryHandleTypeFlagBits'
--     value
--
-- = See Also
--
-- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.ExternalMemoryHandleTypeFlagBits',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ImportMemoryHostPointerInfoEXT = ImportMemoryHostPointerInfoEXT
  { -- | @handleType@ specifies the handle type.
    ImportMemoryHostPointerInfoEXT -> ExternalMemoryHandleTypeFlagBits
handleType :: ExternalMemoryHandleTypeFlagBits
  , -- | @pHostPointer@ is the host pointer to import from.
    ImportMemoryHostPointerInfoEXT -> "hostPointer" ::: Ptr ()
hostPointer :: Ptr ()
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImportMemoryHostPointerInfoEXT)
#endif
deriving instance Show ImportMemoryHostPointerInfoEXT

instance ToCStruct ImportMemoryHostPointerInfoEXT where
  withCStruct :: ImportMemoryHostPointerInfoEXT
-> (Ptr ImportMemoryHostPointerInfoEXT -> IO b) -> IO b
withCStruct x :: ImportMemoryHostPointerInfoEXT
x f :: Ptr ImportMemoryHostPointerInfoEXT -> IO b
f = Int -> Int -> (Ptr ImportMemoryHostPointerInfoEXT -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr ImportMemoryHostPointerInfoEXT -> IO b) -> IO b)
-> (Ptr ImportMemoryHostPointerInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr ImportMemoryHostPointerInfoEXT
p -> Ptr ImportMemoryHostPointerInfoEXT
-> ImportMemoryHostPointerInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ImportMemoryHostPointerInfoEXT
p ImportMemoryHostPointerInfoEXT
x (Ptr ImportMemoryHostPointerInfoEXT -> IO b
f Ptr ImportMemoryHostPointerInfoEXT
p)
  pokeCStruct :: Ptr ImportMemoryHostPointerInfoEXT
-> ImportMemoryHostPointerInfoEXT -> IO b -> IO b
pokeCStruct p :: Ptr ImportMemoryHostPointerInfoEXT
p ImportMemoryHostPointerInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_MEMORY_HOST_POINTER_INFO_EXT)
    Ptr ("hostPointer" ::: Ptr ())
-> ("hostPointer" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT
-> Int -> Ptr ("hostPointer" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("hostPointer" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ExternalMemoryHandleTypeFlagBits
-> ExternalMemoryHandleTypeFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT
-> Int -> Ptr ExternalMemoryHandleTypeFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ExternalMemoryHandleTypeFlagBits)) (ExternalMemoryHandleTypeFlagBits
handleType)
    Ptr ("hostPointer" ::: Ptr ())
-> ("hostPointer" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT
-> Int -> Ptr ("hostPointer" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr ()))) ("hostPointer" ::: Ptr ()
hostPointer)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr ImportMemoryHostPointerInfoEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr ImportMemoryHostPointerInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMPORT_MEMORY_HOST_POINTER_INFO_EXT)
    Ptr ("hostPointer" ::: Ptr ())
-> ("hostPointer" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT
-> Int -> Ptr ("hostPointer" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("hostPointer" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ExternalMemoryHandleTypeFlagBits
-> ExternalMemoryHandleTypeFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT
-> Int -> Ptr ExternalMemoryHandleTypeFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ExternalMemoryHandleTypeFlagBits)) (ExternalMemoryHandleTypeFlagBits
forall a. Zero a => a
zero)
    Ptr ("hostPointer" ::: Ptr ())
-> ("hostPointer" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT
-> Int -> Ptr ("hostPointer" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr ()))) ("hostPointer" ::: Ptr ()
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct ImportMemoryHostPointerInfoEXT where
  peekCStruct :: Ptr ImportMemoryHostPointerInfoEXT
-> IO ImportMemoryHostPointerInfoEXT
peekCStruct p :: Ptr ImportMemoryHostPointerInfoEXT
p = do
    ExternalMemoryHandleTypeFlagBits
handleType <- Ptr ExternalMemoryHandleTypeFlagBits
-> IO ExternalMemoryHandleTypeFlagBits
forall a. Storable a => Ptr a -> IO a
peek @ExternalMemoryHandleTypeFlagBits ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT
-> Int -> Ptr ExternalMemoryHandleTypeFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ExternalMemoryHandleTypeFlagBits))
    "hostPointer" ::: Ptr ()
pHostPointer <- Ptr ("hostPointer" ::: Ptr ()) -> IO ("hostPointer" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr ImportMemoryHostPointerInfoEXT
p Ptr ImportMemoryHostPointerInfoEXT
-> Int -> Ptr ("hostPointer" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr ())))
    ImportMemoryHostPointerInfoEXT -> IO ImportMemoryHostPointerInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImportMemoryHostPointerInfoEXT
 -> IO ImportMemoryHostPointerInfoEXT)
-> ImportMemoryHostPointerInfoEXT
-> IO ImportMemoryHostPointerInfoEXT
forall a b. (a -> b) -> a -> b
$ ExternalMemoryHandleTypeFlagBits
-> ("hostPointer" ::: Ptr ()) -> ImportMemoryHostPointerInfoEXT
ImportMemoryHostPointerInfoEXT
             ExternalMemoryHandleTypeFlagBits
handleType "hostPointer" ::: Ptr ()
pHostPointer

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

instance Zero ImportMemoryHostPointerInfoEXT where
  zero :: ImportMemoryHostPointerInfoEXT
zero = ExternalMemoryHandleTypeFlagBits
-> ("hostPointer" ::: Ptr ()) -> ImportMemoryHostPointerInfoEXT
ImportMemoryHostPointerInfoEXT
           ExternalMemoryHandleTypeFlagBits
forall a. Zero a => a
zero
           "hostPointer" ::: Ptr ()
forall a. Zero a => a
zero


-- | VkMemoryHostPointerPropertiesEXT - Properties of external memory host
-- pointer
--
-- = Description
--
-- The value returned by @memoryTypeBits@ /must/ only include bits that
-- identify memory types which are host visible.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getMemoryHostPointerPropertiesEXT'
data MemoryHostPointerPropertiesEXT = MemoryHostPointerPropertiesEXT
  { -- | @memoryTypeBits@ is a bitmask containing one bit set for every memory
    -- type which the specified host pointer /can/ be imported as.
    MemoryHostPointerPropertiesEXT -> Word32
memoryTypeBits :: Word32 }
  deriving (Typeable, MemoryHostPointerPropertiesEXT
-> MemoryHostPointerPropertiesEXT -> Bool
(MemoryHostPointerPropertiesEXT
 -> MemoryHostPointerPropertiesEXT -> Bool)
-> (MemoryHostPointerPropertiesEXT
    -> MemoryHostPointerPropertiesEXT -> Bool)
-> Eq MemoryHostPointerPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryHostPointerPropertiesEXT
-> MemoryHostPointerPropertiesEXT -> Bool
$c/= :: MemoryHostPointerPropertiesEXT
-> MemoryHostPointerPropertiesEXT -> Bool
== :: MemoryHostPointerPropertiesEXT
-> MemoryHostPointerPropertiesEXT -> Bool
$c== :: MemoryHostPointerPropertiesEXT
-> MemoryHostPointerPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryHostPointerPropertiesEXT)
#endif
deriving instance Show MemoryHostPointerPropertiesEXT

instance ToCStruct MemoryHostPointerPropertiesEXT where
  withCStruct :: MemoryHostPointerPropertiesEXT
-> (("pMemoryHostPointerProperties"
     ::: Ptr MemoryHostPointerPropertiesEXT)
    -> IO b)
-> IO b
withCStruct x :: MemoryHostPointerPropertiesEXT
x f :: ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> IO b
f = Int
-> Int
-> (("pMemoryHostPointerProperties"
     ::: Ptr MemoryHostPointerPropertiesEXT)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pMemoryHostPointerProperties"
   ::: Ptr MemoryHostPointerPropertiesEXT)
  -> IO b)
 -> IO b)
-> (("pMemoryHostPointerProperties"
     ::: Ptr MemoryHostPointerPropertiesEXT)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p -> ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> MemoryHostPointerPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p MemoryHostPointerPropertiesEXT
x (("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> IO b
f "pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p)
  pokeCStruct :: ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> MemoryHostPointerPropertiesEXT -> IO b -> IO b
pokeCStruct p :: "pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p MemoryHostPointerPropertiesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_HOST_POINTER_PROPERTIES_EXT)
    Ptr ("hostPointer" ::: Ptr ())
-> ("hostPointer" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> Int -> Ptr ("hostPointer" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("hostPointer" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
memoryTypeBits)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> IO b -> IO b
pokeZeroCStruct p :: "pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_HOST_POINTER_PROPERTIES_EXT)
    Ptr ("hostPointer" ::: Ptr ())
-> ("hostPointer" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> Int -> Ptr ("hostPointer" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("hostPointer" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct MemoryHostPointerPropertiesEXT where
  peekCStruct :: ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> IO MemoryHostPointerPropertiesEXT
peekCStruct p :: "pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p = do
    Word32
memoryTypeBits <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pMemoryHostPointerProperties"
::: Ptr MemoryHostPointerPropertiesEXT
p ("pMemoryHostPointerProperties"
 ::: Ptr MemoryHostPointerPropertiesEXT)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    MemoryHostPointerPropertiesEXT -> IO MemoryHostPointerPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryHostPointerPropertiesEXT
 -> IO MemoryHostPointerPropertiesEXT)
-> MemoryHostPointerPropertiesEXT
-> IO MemoryHostPointerPropertiesEXT
forall a b. (a -> b) -> a -> b
$ Word32 -> MemoryHostPointerPropertiesEXT
MemoryHostPointerPropertiesEXT
             Word32
memoryTypeBits

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

instance Zero MemoryHostPointerPropertiesEXT where
  zero :: MemoryHostPointerPropertiesEXT
zero = Word32 -> MemoryHostPointerPropertiesEXT
MemoryHostPointerPropertiesEXT
           Word32
forall a. Zero a => a
zero


-- | VkPhysicalDeviceExternalMemoryHostPropertiesEXT - Structure describing
-- external memory host pointer limits that can be supported by an
-- implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceExternalMemoryHostPropertiesEXT'
-- structure describe the following implementation-dependent limits:
--
-- = Description
--
-- If the 'PhysicalDeviceExternalMemoryHostPropertiesEXT' structure is
-- included in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- it is filled with the implementation-dependent limits.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceExternalMemoryHostPropertiesEXT = PhysicalDeviceExternalMemoryHostPropertiesEXT
  { -- | @minImportedHostPointerAlignment@ is the minimum /required/ alignment,
    -- in bytes, for the base address and size of host pointers that /can/ be
    -- imported to a Vulkan memory object.
    PhysicalDeviceExternalMemoryHostPropertiesEXT -> DeviceSize
minImportedHostPointerAlignment :: DeviceSize }
  deriving (Typeable, PhysicalDeviceExternalMemoryHostPropertiesEXT
-> PhysicalDeviceExternalMemoryHostPropertiesEXT -> Bool
(PhysicalDeviceExternalMemoryHostPropertiesEXT
 -> PhysicalDeviceExternalMemoryHostPropertiesEXT -> Bool)
-> (PhysicalDeviceExternalMemoryHostPropertiesEXT
    -> PhysicalDeviceExternalMemoryHostPropertiesEXT -> Bool)
-> Eq PhysicalDeviceExternalMemoryHostPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceExternalMemoryHostPropertiesEXT
-> PhysicalDeviceExternalMemoryHostPropertiesEXT -> Bool
$c/= :: PhysicalDeviceExternalMemoryHostPropertiesEXT
-> PhysicalDeviceExternalMemoryHostPropertiesEXT -> Bool
== :: PhysicalDeviceExternalMemoryHostPropertiesEXT
-> PhysicalDeviceExternalMemoryHostPropertiesEXT -> Bool
$c== :: PhysicalDeviceExternalMemoryHostPropertiesEXT
-> PhysicalDeviceExternalMemoryHostPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceExternalMemoryHostPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceExternalMemoryHostPropertiesEXT

instance ToCStruct PhysicalDeviceExternalMemoryHostPropertiesEXT where
  withCStruct :: PhysicalDeviceExternalMemoryHostPropertiesEXT
-> (Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceExternalMemoryHostPropertiesEXT
x f :: Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT -> IO b)
 -> IO b)
-> (Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p -> Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> PhysicalDeviceExternalMemoryHostPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p PhysicalDeviceExternalMemoryHostPropertiesEXT
x (Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT -> IO b
f Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> PhysicalDeviceExternalMemoryHostPropertiesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p PhysicalDeviceExternalMemoryHostPropertiesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_HOST_PROPERTIES_EXT)
    Ptr ("hostPointer" ::: Ptr ())
-> ("hostPointer" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> Int -> Ptr ("hostPointer" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("hostPointer" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) (DeviceSize
minImportedHostPointerAlignment)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_HOST_PROPERTIES_EXT)
    Ptr ("hostPointer" ::: Ptr ())
-> ("hostPointer" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> Int -> Ptr ("hostPointer" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("hostPointer" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) (DeviceSize
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceExternalMemoryHostPropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> IO PhysicalDeviceExternalMemoryHostPropertiesEXT
peekCStruct p :: Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p = do
    DeviceSize
minImportedHostPointerAlignment <- Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
p Ptr PhysicalDeviceExternalMemoryHostPropertiesEXT
-> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
    PhysicalDeviceExternalMemoryHostPropertiesEXT
-> IO PhysicalDeviceExternalMemoryHostPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceExternalMemoryHostPropertiesEXT
 -> IO PhysicalDeviceExternalMemoryHostPropertiesEXT)
-> PhysicalDeviceExternalMemoryHostPropertiesEXT
-> IO PhysicalDeviceExternalMemoryHostPropertiesEXT
forall a b. (a -> b) -> a -> b
$ DeviceSize -> PhysicalDeviceExternalMemoryHostPropertiesEXT
PhysicalDeviceExternalMemoryHostPropertiesEXT
             DeviceSize
minImportedHostPointerAlignment

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

instance Zero PhysicalDeviceExternalMemoryHostPropertiesEXT where
  zero :: PhysicalDeviceExternalMemoryHostPropertiesEXT
zero = DeviceSize -> PhysicalDeviceExternalMemoryHostPropertiesEXT
PhysicalDeviceExternalMemoryHostPropertiesEXT
           DeviceSize
forall a. Zero a => a
zero


type EXT_EXTERNAL_MEMORY_HOST_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_EXTERNAL_MEMORY_HOST_SPEC_VERSION"
pattern EXT_EXTERNAL_MEMORY_HOST_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_EXTERNAL_MEMORY_HOST_SPEC_VERSION :: a
$mEXT_EXTERNAL_MEMORY_HOST_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_EXTERNAL_MEMORY_HOST_SPEC_VERSION = 1


type EXT_EXTERNAL_MEMORY_HOST_EXTENSION_NAME = "VK_EXT_external_memory_host"

-- No documentation found for TopLevel "VK_EXT_EXTERNAL_MEMORY_HOST_EXTENSION_NAME"
pattern EXT_EXTERNAL_MEMORY_HOST_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_EXTERNAL_MEMORY_HOST_EXTENSION_NAME :: a
$mEXT_EXTERNAL_MEMORY_HOST_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_EXTERNAL_MEMORY_HOST_EXTENSION_NAME = "VK_EXT_external_memory_host"