vulkan-3.24.4: Bindings to the Vulkan graphics API.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Vulkan.Extensions.VK_EXT_metal_objects

Description

Name

VK_EXT_metal_objects - device extension

VK_EXT_metal_objects

Name String
VK_EXT_metal_objects
Extension Type
Device extension
Registered Extension Number
312
Revision
1
Extension and Version Dependencies
  • Requires support for Vulkan 1.0
Contact
Extension Proposal
VK_EXT_metal_objects

Other Extension Metadata

Last Modified Date
2022-05-28
IP Status
No known IP claims.
Contributors
  • Bill Hollings, The Brenwill Workshop Ltd.
  • Dzmitry Malyshau, Mozilla Corp.

Description

In a Vulkan implementation that is layered on top of Metal on Apple device platforms, this extension provides the ability to import and export the underlying Metal objects associated with specific Vulkan objects.

As detailed in the extension proposal document, this extension adds one new Vulkan command, exportMetalObjectsEXT, to export underlying Metal objects from Vulkan objects, and supports importing the appropriate existing Metal objects when creating Vulkan objects of types DeviceMemory, Image, Semaphore, and Event,

The intent is that this extension will be advertised and supported only on implementations that are layered on top of Metal on Apple device platforms.

New Base Types

New Commands

New Structures

New Enums

New Bitmasks

New Enum Constants

Issues

None.

Version History

  • Revision 1, 2022-05-28 (Bill Hollings)

    • Initial draft.
    • Incorporated feedback from review by the Vulkan Working Group. Renamed many structures, moved import/export of MTLBuffer to VkDeviceMemory, added export of MTLSharedEvent, added import of MTLSharedEvent for VkSemaphore and VkEvent, and changed used bit mask fields to individual bit fields to simplify Valid Usage rules.

See Also

IOSurfaceRef, MTLBuffer_id, MTLCommandQueue_id, MTLDevice_id, MTLSharedEvent_id, MTLTexture_id, ExportMetalBufferInfoEXT, ExportMetalCommandQueueInfoEXT, ExportMetalDeviceInfoEXT, ExportMetalIOSurfaceInfoEXT, ExportMetalObjectCreateInfoEXT, ExportMetalObjectTypeFlagBitsEXT, ExportMetalObjectTypeFlagsEXT, ExportMetalObjectsInfoEXT, ExportMetalSharedEventInfoEXT, ExportMetalTextureInfoEXT, ImportMetalBufferInfoEXT, ImportMetalIOSurfaceInfoEXT, ImportMetalSharedEventInfoEXT, ImportMetalTextureInfoEXT, exportMetalObjectsEXT

Document Notes

For more information, see the Vulkan Specification

This page is a generated document. Fixes and changes should be made to the generator scripts, not directly.

Synopsis

Documentation

exportMetalObjectsEXT Source #

Arguments

:: forall a io. (Extendss ExportMetalObjectsInfoEXT a, PokeChain a, PeekChain a, MonadIO io) 
=> Device

device is the device that created the Vulkan objects.

device must be a valid Device handle

-> io (ExportMetalObjectsInfoEXT a) 

vkExportMetalObjectsEXT - Export Metal objects from the corresponding Vulkan objects

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, Device, ExportMetalObjectsInfoEXT

data ExportMetalObjectCreateInfoEXT Source #

VkExportMetalObjectCreateInfoEXT - Structure that identifies the Metal objects that can be exported from Vulkan objects

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, ExportMetalObjectTypeFlagBitsEXT, StructureType

Constructors

ExportMetalObjectCreateInfoEXT 

Fields

Instances

Instances details
Storable ExportMetalObjectCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ExportMetalObjectCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ExportMetalObjectCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ExportMetalObjectCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ExportMetalObjectCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ExportMetalObjectCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ExportMetalObjectsInfoEXT (es :: [Type]) Source #

VkExportMetalObjectsInfoEXT - Structure whose pNext chain identifies Vulkan objects and corresponding Metal objects

Valid Usage

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, StructureType, exportMetalObjectsEXT

Constructors

ExportMetalObjectsInfoEXT 

Fields

  • next :: Chain es

    pNext is NULL or a pointer to a structure extending this structure.

Instances

Instances details
Extensible ExportMetalObjectsInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Methods

extensibleTypeName :: String Source #

getNext :: forall (es :: [Type]). ExportMetalObjectsInfoEXT es -> Chain es Source #

setNext :: forall (ds :: [Type]) (es :: [TYPE LiftedRep]). ExportMetalObjectsInfoEXT ds -> Chain es -> ExportMetalObjectsInfoEXT es Source #

extends :: forall e b proxy. Typeable e => proxy e -> (Extends ExportMetalObjectsInfoEXT e => b) -> Maybe b Source #

Show (Chain es) => Show (ExportMetalObjectsInfoEXT es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

(Extendss ExportMetalObjectsInfoEXT es, PeekChain es) => FromCStruct (ExportMetalObjectsInfoEXT es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

(Extendss ExportMetalObjectsInfoEXT es, PokeChain es) => ToCStruct (ExportMetalObjectsInfoEXT es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

es ~ ('[] :: [Type]) => Zero (ExportMetalObjectsInfoEXT es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ExportMetalDeviceInfoEXT Source #

VkExportMetalDeviceInfoEXT - Structure that identifies a VkDevice object and corresponding Metal MTLDevice object

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, StructureType

Constructors

ExportMetalDeviceInfoEXT 

Fields

  • mtlDevice :: MTLDevice_id

    mtlDevice is the Metal id<MTLDevice> object underlying the PhysicalDevice associated with the Device object identified in the call. The implementation will return the MTLDevice in this member, or it will return NULL if no MTLDevice could be found underlying the PhysicalDevice object.

Instances

Instances details
Storable ExportMetalDeviceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ExportMetalDeviceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ExportMetalDeviceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ExportMetalDeviceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ExportMetalDeviceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ExportMetalDeviceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ExportMetalCommandQueueInfoEXT Source #

VkExportMetalCommandQueueInfoEXT - Structure that identifies a VkQueue object and corresponding Metal MTLCommandQueue object

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, Queue, StructureType

Constructors

ExportMetalCommandQueueInfoEXT 

Fields

  • queue :: Ptr Queue_T

    queue is a Queue.

    queue must be a valid Queue handle

  • mtlCommandQueue :: MTLCommandQueue_id

    mtlCommandQueue is the Metal id<MTLCommandQueue> object underlying the Queue object in queue. The implementation will return the MTLCommandQueue in this member, or it will return NULL if no MTLCommandQueue could be found underlying the Queue object.

Instances

Instances details
Storable ExportMetalCommandQueueInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ExportMetalCommandQueueInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ExportMetalCommandQueueInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ExportMetalCommandQueueInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ExportMetalCommandQueueInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ExportMetalCommandQueueInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ExportMetalBufferInfoEXT Source #

VkExportMetalBufferInfoEXT - Structure that identifies a VkDeviceMemory object and corresponding Metal MTLBuffer object

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, DeviceMemory, StructureType

Constructors

ExportMetalBufferInfoEXT 

Fields

Instances

Instances details
Storable ExportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ExportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ExportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ExportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ExportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ExportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ImportMetalBufferInfoEXT Source #

VkImportMetalBufferInfoEXT - Structure that identifies a Metal MTLBuffer object to use when creating a VkDeviceMemory object.

Description

The app must ensure that the configuration of the id<MTLBuffer> object is compatible with the configuration of the DeviceMemory. Failure to do so results in undefined behavior.

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, StructureType

Constructors

ImportMetalBufferInfoEXT 

Fields

Instances

Instances details
Storable ImportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ImportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ImportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ImportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ImportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ImportMetalBufferInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ExportMetalTextureInfoEXT Source #

VkExportMetalTextureInfoEXT - Structure that identifies a VkImage, VkImageView, or VkBufferView object and corresponding Metal MTLTexture object

Valid Usage (Implicit)

  • If image is not NULL_HANDLE, image must be a valid Image handle
  • If imageView is not NULL_HANDLE, imageView must be a valid ImageView handle
  • If bufferView is not NULL_HANDLE, bufferView must be a valid BufferView handle
  • plane must be a valid ImageAspectFlagBits value
  • Each of bufferView, image, and imageView that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

See Also

VK_EXT_metal_objects, BufferView, Image, ImageAspectFlagBits, ImageView, StructureType

Constructors

ExportMetalTextureInfoEXT 

Fields

Instances

Instances details
Storable ExportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ExportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ExportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ExportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ExportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ExportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ImportMetalTextureInfoEXT Source #

VkImportMetalTextureInfoEXT - Structure that identifies Metal MTLTexture objects to use when creating a VkImage.

Description

The pNext chain must include one ImportMetalTextureInfoEXT structure for each plane in the Image. The app must ensure that the configuration of the Metal id<MTLTexture> objects are compatible with the configuration of the Image. Failure to do so results in undefined behavior.

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, ImageAspectFlagBits, StructureType

Constructors

ImportMetalTextureInfoEXT 

Fields

Instances

Instances details
Storable ImportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ImportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ImportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ImportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ImportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ImportMetalTextureInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ExportMetalIOSurfaceInfoEXT Source #

VkExportMetalIOSurfaceInfoEXT - Structure that identifies a VkImage object and corresponding Metal IOSurfaceRef object

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, Image, StructureType

Constructors

ExportMetalIOSurfaceInfoEXT 

Fields

Instances

Instances details
Storable ExportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ExportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ExportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ExportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ExportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ExportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ImportMetalIOSurfaceInfoEXT Source #

VkImportMetalIOSurfaceInfoEXT - Structure that identifies a VkImage object and corresponding Metal IOSurfaceRef object to use.

Description

If ioSurface is not NULL_HANDLE, it will be used to underlie the Image. If ioSurface is NULL_HANDLE, the implementation will create a new IOSurface to underlie the Image.

If provided, the app must ensure that the configuration of the IOSurfaceRef object is compatible with the configuration of the Image. Failure to do so results in undefined behavior.

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, StructureType

Constructors

ImportMetalIOSurfaceInfoEXT 

Fields

Instances

Instances details
Storable ImportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ImportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ImportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ImportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ImportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ImportMetalIOSurfaceInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ExportMetalSharedEventInfoEXT Source #

VkExportMetalSharedEventInfoEXT - Structure that identifies a VkSemaphore or VkEvent object and corresponding Metal MTLSharedEvent object

Valid Usage (Implicit)

  • If semaphore is not NULL_HANDLE, semaphore must be a valid Semaphore handle
  • If event is not NULL_HANDLE, event must be a valid Event handle
  • Both of event, and semaphore that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

See Also

VK_EXT_metal_objects, Event, Semaphore, StructureType

Constructors

ExportMetalSharedEventInfoEXT 

Fields

Instances

Instances details
Storable ExportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ExportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ExportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ExportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ExportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ExportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

data ImportMetalSharedEventInfoEXT Source #

VkImportMetalSharedEventInfoEXT - Structure that identifies a VkSemaphore or VkEvent object and corresponding Metal Shared Event object to use.

Description

If the pNext chain of the SemaphoreCreateInfo structure includes both ImportMetalSharedEventInfoEXT and SemaphoreTypeCreateInfo, the signaledValue property of the imported id<MTLSharedEvent> object will be set to initialValue of SemaphoreTypeCreateInfo.

Valid Usage (Implicit)

See Also

VK_EXT_metal_objects, StructureType

Constructors

ImportMetalSharedEventInfoEXT 

Fields

Instances

Instances details
Storable ImportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ImportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ImportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

FromCStruct ImportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

ToCStruct ImportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ImportMetalSharedEventInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

newtype ExportMetalObjectTypeFlagBitsEXT Source #

VkExportMetalObjectTypeFlagBitsEXT - Bitmask specifying Metal object types that can be exported from a Vulkan object

See Also

VK_EXT_metal_objects, ExportMetalObjectCreateInfoEXT, ExportMetalObjectTypeFlagsEXT

Instances

Instances details
Storable ExportMetalObjectTypeFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Bits ExportMetalObjectTypeFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Methods

(.&.) :: ExportMetalObjectTypeFlagBitsEXT -> ExportMetalObjectTypeFlagBitsEXT -> ExportMetalObjectTypeFlagBitsEXT #

(.|.) :: ExportMetalObjectTypeFlagBitsEXT -> ExportMetalObjectTypeFlagBitsEXT -> ExportMetalObjectTypeFlagBitsEXT #

xor :: ExportMetalObjectTypeFlagBitsEXT -> ExportMetalObjectTypeFlagBitsEXT -> ExportMetalObjectTypeFlagBitsEXT #

complement :: ExportMetalObjectTypeFlagBitsEXT -> ExportMetalObjectTypeFlagBitsEXT #

shift :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

rotate :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

zeroBits :: ExportMetalObjectTypeFlagBitsEXT #

bit :: Int -> ExportMetalObjectTypeFlagBitsEXT #

setBit :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

clearBit :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

complementBit :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

testBit :: ExportMetalObjectTypeFlagBitsEXT -> Int -> Bool #

bitSizeMaybe :: ExportMetalObjectTypeFlagBitsEXT -> Maybe Int #

bitSize :: ExportMetalObjectTypeFlagBitsEXT -> Int #

isSigned :: ExportMetalObjectTypeFlagBitsEXT -> Bool #

shiftL :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

unsafeShiftL :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

shiftR :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

unsafeShiftR :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

rotateL :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

rotateR :: ExportMetalObjectTypeFlagBitsEXT -> Int -> ExportMetalObjectTypeFlagBitsEXT #

popCount :: ExportMetalObjectTypeFlagBitsEXT -> Int #

FiniteBits ExportMetalObjectTypeFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Read ExportMetalObjectTypeFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Show ExportMetalObjectTypeFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Eq ExportMetalObjectTypeFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Ord ExportMetalObjectTypeFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

Zero ExportMetalObjectTypeFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_metal_objects

pattern EXT_METAL_OBJECTS_SPEC_VERSION :: forall a. Integral a => a Source #

type EXT_METAL_OBJECTS_EXTENSION_NAME = "VK_EXT_metal_objects" Source #

pattern EXT_METAL_OBJECTS_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #