{-# 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 (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)
data ExternalMemoryImageCreateInfoNV = ExternalMemoryImageCreateInfoNV
{
ExternalMemoryImageCreateInfoNV -> ExternalMemoryHandleTypeFlagsNV
handleTypes :: ExternalMemoryHandleTypeFlagsNV }
deriving (Typeable, ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> Bool
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 = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ExternalMemoryImageCreateInfoNV
p -> 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
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryImageCreateInfoNV
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 ExternalMemoryImageCreateInfoNV
p 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
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExternalMemoryImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: 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 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ExternalMemoryHandleTypeFlagsNV))
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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 = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ExternalMemoryImageCreateInfoNV
-> ExternalMemoryImageCreateInfoNV -> IO ()
poke Ptr ExternalMemoryImageCreateInfoNV
ptr ExternalMemoryImageCreateInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExternalMemoryImageCreateInfoNV
ptr ExternalMemoryImageCreateInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ExternalMemoryImageCreateInfoNV where
zero :: ExternalMemoryImageCreateInfoNV
zero = ExternalMemoryHandleTypeFlagsNV -> ExternalMemoryImageCreateInfoNV
ExternalMemoryImageCreateInfoNV
forall a. Zero a => a
zero
data ExportMemoryAllocateInfoNV = ExportMemoryAllocateInfoNV
{
ExportMemoryAllocateInfoNV -> ExternalMemoryHandleTypeFlagsNV
handleTypes :: ExternalMemoryHandleTypeFlagsNV }
deriving (Typeable, ExportMemoryAllocateInfoNV -> ExportMemoryAllocateInfoNV -> Bool
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 = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr ExportMemoryAllocateInfoNV
p -> 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
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryAllocateInfoNV
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 ExportMemoryAllocateInfoNV
p 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
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr ExportMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: 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 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr ExternalMemoryHandleTypeFlagsNV))
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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 = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr ExportMemoryAllocateInfoNV
-> ExportMemoryAllocateInfoNV -> IO ()
poke Ptr ExportMemoryAllocateInfoNV
ptr ExportMemoryAllocateInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr ExportMemoryAllocateInfoNV
ptr ExportMemoryAllocateInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero ExportMemoryAllocateInfoNV where
zero :: ExportMemoryAllocateInfoNV
zero = ExternalMemoryHandleTypeFlagsNV -> ExportMemoryAllocateInfoNV
ExportMemoryAllocateInfoNV
forall a. Zero a => a
zero
type NV_EXTERNAL_MEMORY_SPEC_VERSION = 1
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 -> ((# #) -> r) -> ((# #) -> r) -> r
NV_EXTERNAL_MEMORY_SPEC_VERSION = 1
type NV_EXTERNAL_MEMORY_EXTENSION_NAME = "VK_NV_external_memory"
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 -> ((# #) -> r) -> ((# #) -> r) -> r
NV_EXTERNAL_MEMORY_EXTENSION_NAME = "VK_NV_external_memory"