{-# language CPP #-}
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 (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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
--
-- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagsNV',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data ExternalMemoryImageCreateInfoNV = ExternalMemoryImageCreateInfoNV
  { -- | @handleTypes@ is a bitmask of
    -- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.ExternalMemoryHandleTypeFlagBitsNV'
    -- specifying one or more external memory handle types.
    --
    -- @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 :: ExternalMemoryImageCreateInfoNV
-> (Ptr ExternalMemoryImageCreateInfoNV -> IO b) -> IO b
withCStruct x :: ExternalMemoryImageCreateInfoNV
x f :: Ptr ExternalMemoryImageCreateInfoNV -> IO b
f = Int -> Int -> (Ptr ExternalMemoryImageCreateInfoNV -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr ExternalMemoryImageCreateInfoNV -> IO b) -> IO b)
-> (Ptr ExternalMemoryImageCreateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: 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 :: Ptr ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr ExternalMemoryImageCreateInfoNV
p ExternalMemoryImageCreateInfoNV{..} f :: 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` 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` 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` 16 :: Ptr ExternalMemoryHandleTypeFlagsNV)) (ExternalMemoryHandleTypeFlagsNV
handleTypes)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr ExternalMemoryImageCreateInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr ExternalMemoryImageCreateInfoNV
p f :: 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` 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` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct ExternalMemoryImageCreateInfoNV where
  peekCStruct :: Ptr ExternalMemoryImageCreateInfoNV
-> IO ExternalMemoryImageCreateInfoNV
peekCStruct p :: Ptr ExternalMemoryImageCreateInfoNV
p = do
    ExternalMemoryHandleTypeFlagsNV
handleTypes <- Ptr ExternalMemoryHandleTypeFlagsNV
-> IO ExternalMemoryHandleTypeFlagsNV
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` 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
_ = 24
  alignment :: ExternalMemoryImageCreateInfoNV -> Int
alignment ~ExternalMemoryImageCreateInfoNV
_ = 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 :: Ptr ExternalMemoryImageCreateInfoNV
ptr poked :: 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
--
-- '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'.
    --
    -- @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 :: ExportMemoryAllocateInfoNV
-> (Ptr ExportMemoryAllocateInfoNV -> IO b) -> IO b
withCStruct x :: ExportMemoryAllocateInfoNV
x f :: Ptr ExportMemoryAllocateInfoNV -> IO b
f = Int -> Int -> (Ptr ExportMemoryAllocateInfoNV -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr ExportMemoryAllocateInfoNV -> IO b) -> IO b)
-> (Ptr ExportMemoryAllocateInfoNV -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: 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 :: Ptr ExportMemoryAllocateInfoNV
-> ExportMemoryAllocateInfoNV -> IO b -> IO b
pokeCStruct p :: Ptr ExportMemoryAllocateInfoNV
p ExportMemoryAllocateInfoNV{..} f :: 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` 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` 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` 16 :: Ptr ExternalMemoryHandleTypeFlagsNV)) (ExternalMemoryHandleTypeFlagsNV
handleTypes)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr ExportMemoryAllocateInfoNV -> IO b -> IO b
pokeZeroCStruct p :: Ptr ExportMemoryAllocateInfoNV
p f :: 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` 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` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct ExportMemoryAllocateInfoNV where
  peekCStruct :: Ptr ExportMemoryAllocateInfoNV -> IO ExportMemoryAllocateInfoNV
peekCStruct p :: Ptr ExportMemoryAllocateInfoNV
p = do
    ExternalMemoryHandleTypeFlagsNV
handleTypes <- Ptr ExternalMemoryHandleTypeFlagsNV
-> IO ExternalMemoryHandleTypeFlagsNV
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` 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
_ = 24
  alignment :: ExportMemoryAllocateInfoNV -> Int
alignment ~ExportMemoryAllocateInfoNV
_ = 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 :: Ptr ExportMemoryAllocateInfoNV
ptr poked :: 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 :: 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 :: 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"