{-# language CPP #-}
-- | = Name
--
-- VK_NV_external_memory - device extension
--
-- == VK_NV_external_memory
--
-- [__Name String__]
--     @VK_NV_external_memory@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     57
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_NV_external_memory_capabilities@ to be enabled for
--         any device-level functionality
--
-- [__Deprecation state__]
--
--     -   /Deprecated/ by @VK_KHR_external_memory@ extension
--
--         -   Which in turn was /promoted/ to
--             <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#versions-1.1-promotions Vulkan 1.1>
--
-- [__Contact__]
--
--     -   James Jones
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_NV_external_memory] @cubanismo%0A*Here describe the issue or question you have about the VK_NV_external_memory extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2016-08-19
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   James Jones, NVIDIA
--
--     -   Carsten Rohde, NVIDIA
--
-- == Description
--
-- Applications may wish to export memory to other Vulkan instances or
-- other APIs, or import memory from other Vulkan instances or other APIs
-- to enable Vulkan workloads to be split up across application module,
-- process, or API boundaries. This extension enables applications to
-- create exportable Vulkan memory objects such that the underlying
-- resources can be referenced outside the Vulkan instance that created
-- them.
--
-- == New Structures
--
-- -   Extending 'Vulkan.Core10.Image.ImageCreateInfo':
--
--     -   'ExternalMemoryImageCreateInfoNV'
--
-- -   Extending 'Vulkan.Core10.Memory.MemoryAllocateInfo':
--
--     -   'ExportMemoryAllocateInfoNV'
--
-- == New Enum Constants
--
-- -   'NV_EXTERNAL_MEMORY_EXTENSION_NAME'
--
-- -   'NV_EXTERNAL_MEMORY_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO_NV'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO_NV'
--
-- == Issues
--
-- 1) If memory objects are shared between processes and APIs, is this
-- considered aliasing according to the rules outlined in the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-memory-aliasing Memory Aliasing>
-- section?
--
-- __RESOLVED__: Yes, but strict exceptions to the rules are added to allow
-- some forms of aliasing in these cases. Further, other extensions may
-- build upon these new aliasing rules to define specific support usage
-- within Vulkan for imported native memory objects, or memory objects from
-- other APIs.
--
-- 2) Are new image layouts or metadata required to specify image layouts
-- and layout transitions compatible with non-Vulkan APIs, or with other
-- instances of the same Vulkan driver?
--
-- __RESOLVED__: No. Separate instances of the same Vulkan driver running
-- on the same GPU should have identical internal layout semantics, so
-- applications have the tools they need to ensure views of images are
-- consistent between the two instances. Other APIs will fall into two
-- categories: Those that are Vulkan compatible (a term to be defined by
-- subsequent interopability extensions), or Vulkan incompatible. When
-- sharing images with Vulkan incompatible APIs, the Vulkan image must be
-- transitioned to the
-- 'Vulkan.Core10.Enums.ImageLayout.IMAGE_LAYOUT_GENERAL' layout before
-- handing it off to the external API.
--
-- Note this does not attempt to address cross-device transitions, nor
-- transitions to engines on the same device which are not visible within
-- the Vulkan API. Both of these are beyond the scope of this extension.
--
-- == Examples
--
-- >     // TODO: Write some sample code here.
--
-- == Version History
--
-- -   Revision 1, 2016-08-19 (James Jones)
--
--     -   Initial draft
--
-- == See Also
--
-- 'ExportMemoryAllocateInfoNV', 'ExternalMemoryImageCreateInfoNV'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_NV_external_memory Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_NV_external_memory  ( ExternalMemoryImageCreateInfoNV(..)
                                                , ExportMemoryAllocateInfoNV(..)
                                                , NV_EXTERNAL_MEMORY_SPEC_VERSION
                                                , pattern NV_EXTERNAL_MEMORY_SPEC_VERSION
                                                , NV_EXTERNAL_MEMORY_EXTENSION_NAME
                                                , pattern NV_EXTERNAL_MEMORY_EXTENSION_NAME
                                                , ExternalMemoryHandleTypeFlagBitsNV(..)
                                                , ExternalMemoryHandleTypeFlagsNV
                                                ) where

import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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 Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Extensions.VK_NV_external_memory_capabilities (ExternalMemoryHandleTypeFlagsNV)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO_NV))
import Vulkan.Extensions.VK_NV_external_memory_capabilities (ExternalMemoryHandleTypeFlagBitsNV(..))
import Vulkan.Extensions.VK_NV_external_memory_capabilities (ExternalMemoryHandleTypeFlagsNV)
-- | VkExternalMemoryImageCreateInfoNV - Specify that an image may be backed
-- by external memory
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_external_memory VK_NV_external_memory>,
-- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagsNV',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ExternalMemoryImageCreateInfoNV = ExternalMemoryImageCreateInfoNV
  { -- | @handleTypes@ is zero or a bitmask of
    -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagBitsNV'
    -- specifying one or more external memory handle types.
    --
    -- #VUID-VkExternalMemoryImageCreateInfoNV-handleTypes-parameter#
    -- @handleTypes@ /must/ be a valid combination of
    -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagBitsNV'
    -- values
    ExternalMemoryImageCreateInfoNV -> ExternalMemoryHandleTypeFlagsNV
handleTypes :: ExternalMemoryHandleTypeFlagsNV }
  deriving (Typeable, ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> Bool
(ExternalMemoryImageCreateInfoNV
 -> ExternalMemoryImageCreateInfoNV -> Bool)
-> (ExternalMemoryImageCreateInfoNV
    -> ExternalMemoryImageCreateInfoNV -> Bool)
-> Eq ExternalMemoryImageCreateInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> Bool
$c/= :: ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> Bool
== :: ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> Bool
$c== :: ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ExternalMemoryImageCreateInfoNV)
#endif
deriving instance Show ExternalMemoryImageCreateInfoNV

instance ToCStruct ExternalMemoryImageCreateInfoNV where
  withCStruct :: forall b.
ExternalMemoryImageCreateInfoNV
-> (Ptr ExternalMemoryImageCreateInfoNV -> IO b) -> IO b
withCStruct ExternalMemoryImageCreateInfoNV
x Ptr ExternalMemoryImageCreateInfoNV -> IO b
f = Int -> (Ptr ExternalMemoryImageCreateInfoNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr ExternalMemoryImageCreateInfoNV -> IO b) -> IO b)
-> (Ptr ExternalMemoryImageCreateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr ExternalMemoryImageCreateInfoNV
p -> Ptr ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExternalMemoryImageCreateInfoNV
p ExternalMemoryImageCreateInfoNV
x (Ptr ExternalMemoryImageCreateInfoNV -> IO b
f Ptr ExternalMemoryImageCreateInfoNV
p)
  pokeCStruct :: forall b.
Ptr ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> IO b -> IO b
pokeCStruct Ptr ExternalMemoryImageCreateInfoNV
p ExternalMemoryImageCreateInfoNV{ExternalMemoryHandleTypeFlagsNV
handleTypes :: ExternalMemoryHandleTypeFlagsNV
$sel:handleTypes:ExternalMemoryImageCreateInfoNV :: ExternalMemoryImageCreateInfoNV -> ExternalMemoryHandleTypeFlagsNV
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryImageCreateInfoNV
p Ptr ExternalMemoryImageCreateInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryImageCreateInfoNV
p Ptr ExternalMemoryImageCreateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ExternalMemoryHandleTypeFlagsNV
-> ExternalMemoryHandleTypeFlagsNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryImageCreateInfoNV
p Ptr ExternalMemoryImageCreateInfoNV
-> Int -> Ptr ExternalMemoryHandleTypeFlagsNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ExternalMemoryHandleTypeFlagsNV)) (ExternalMemoryHandleTypeFlagsNV
handleTypes)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr ExternalMemoryImageCreateInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr ExternalMemoryImageCreateInfoNV
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryImageCreateInfoNV
p Ptr ExternalMemoryImageCreateInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryImageCreateInfoNV
p Ptr ExternalMemoryImageCreateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

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

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

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


-- | VkExportMemoryAllocateInfoNV - Specify memory handle types that may be
-- exported
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_external_memory VK_NV_external_memory>,
-- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagsNV',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ExportMemoryAllocateInfoNV = ExportMemoryAllocateInfoNV
  { -- | @handleTypes@ is a bitmask of
    -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagBitsNV'
    -- specifying one or more memory handle types that /may/ be exported.
    -- Multiple handle types /may/ be requested for the same allocation as long
    -- as they are compatible, as reported by
    -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.getPhysicalDeviceExternalImageFormatPropertiesNV'.
    --
    -- #VUID-VkExportMemoryAllocateInfoNV-handleTypes-parameter# @handleTypes@
    -- /must/ be a valid combination of
    -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagBitsNV'
    -- values
    ExportMemoryAllocateInfoNV -> ExternalMemoryHandleTypeFlagsNV
handleTypes :: ExternalMemoryHandleTypeFlagsNV }
  deriving (Typeable, ExportMemoryAllocateInfoNV -> ExportMemoryAllocateInfoNV -> Bool
(ExportMemoryAllocateInfoNV -> ExportMemoryAllocateInfoNV -> Bool)
-> (ExportMemoryAllocateInfoNV
    -> ExportMemoryAllocateInfoNV -> Bool)
-> Eq ExportMemoryAllocateInfoNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportMemoryAllocateInfoNV -> ExportMemoryAllocateInfoNV -> Bool
$c/= :: ExportMemoryAllocateInfoNV -> ExportMemoryAllocateInfoNV -> Bool
== :: ExportMemoryAllocateInfoNV -> ExportMemoryAllocateInfoNV -> Bool
$c== :: ExportMemoryAllocateInfoNV -> ExportMemoryAllocateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ExportMemoryAllocateInfoNV)
#endif
deriving instance Show ExportMemoryAllocateInfoNV

instance ToCStruct ExportMemoryAllocateInfoNV where
  withCStruct :: forall b.
ExportMemoryAllocateInfoNV
-> (Ptr ExportMemoryAllocateInfoNV -> IO b) -> IO b
withCStruct ExportMemoryAllocateInfoNV
x Ptr ExportMemoryAllocateInfoNV -> IO b
f = Int -> (Ptr ExportMemoryAllocateInfoNV -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr ExportMemoryAllocateInfoNV -> IO b) -> IO b)
-> (Ptr ExportMemoryAllocateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr ExportMemoryAllocateInfoNV
p -> Ptr ExportMemoryAllocateInfoNV
-> ExportMemoryAllocateInfoNV -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExportMemoryAllocateInfoNV
p ExportMemoryAllocateInfoNV
x (Ptr ExportMemoryAllocateInfoNV -> IO b
f Ptr ExportMemoryAllocateInfoNV
p)
  pokeCStruct :: forall b.
Ptr ExportMemoryAllocateInfoNV
-> ExportMemoryAllocateInfoNV -> IO b -> IO b
pokeCStruct Ptr ExportMemoryAllocateInfoNV
p ExportMemoryAllocateInfoNV{ExternalMemoryHandleTypeFlagsNV
handleTypes :: ExternalMemoryHandleTypeFlagsNV
$sel:handleTypes:ExportMemoryAllocateInfoNV :: ExportMemoryAllocateInfoNV -> ExternalMemoryHandleTypeFlagsNV
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryAllocateInfoNV
p Ptr ExportMemoryAllocateInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryAllocateInfoNV
p Ptr ExportMemoryAllocateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ExternalMemoryHandleTypeFlagsNV
-> ExternalMemoryHandleTypeFlagsNV -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryAllocateInfoNV
p Ptr ExportMemoryAllocateInfoNV
-> Int -> Ptr ExternalMemoryHandleTypeFlagsNV
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ExternalMemoryHandleTypeFlagsNV)) (ExternalMemoryHandleTypeFlagsNV
handleTypes)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr ExportMemoryAllocateInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr ExportMemoryAllocateInfoNV
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryAllocateInfoNV
p Ptr ExportMemoryAllocateInfoNV -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO_NV)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryAllocateInfoNV
p Ptr ExportMemoryAllocateInfoNV -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

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

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

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


type NV_EXTERNAL_MEMORY_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_NV_EXTERNAL_MEMORY_SPEC_VERSION"
pattern NV_EXTERNAL_MEMORY_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_EXTERNAL_MEMORY_SPEC_VERSION :: forall a. Integral a => a
$mNV_EXTERNAL_MEMORY_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_EXTERNAL_MEMORY_SPEC_VERSION = 1


type NV_EXTERNAL_MEMORY_EXTENSION_NAME = "VK_NV_external_memory"

-- No documentation found for TopLevel "VK_NV_EXTERNAL_MEMORY_EXTENSION_NAME"
pattern NV_EXTERNAL_MEMORY_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_EXTERNAL_MEMORY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_EXTERNAL_MEMORY_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
NV_EXTERNAL_MEMORY_EXTENSION_NAME = "VK_NV_external_memory"