vulkan-3.3.1: Bindings to the Vulkan graphics API.
Safe HaskellNone
LanguageHaskell2010

Vulkan.Core10.OtherTypes

Synopsis

Documentation

data MemoryBarrier Source #

VkMemoryBarrier - Structure specifying a global memory barrier

Description

The first access scope is limited to access types in the source access mask specified by srcAccessMask.

The second access scope is limited to access types in the destination access mask specified by dstAccessMask.

Valid Usage (Implicit)

See Also

AccessFlags, StructureType, cmdPipelineBarrier, cmdWaitEvents

Constructors

MemoryBarrier 

Fields

Instances

Instances details
Eq MemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Show MemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Generic MemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Associated Types

type Rep MemoryBarrier :: Type -> Type #

Storable MemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

FromCStruct MemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

ToCStruct MemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Zero MemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

type Rep MemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

type Rep MemoryBarrier = D1 ('MetaData "MemoryBarrier" "Vulkan.Core10.OtherTypes" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "MemoryBarrier" 'PrefixI 'True) (S1 ('MetaSel ('Just "srcAccessMask") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccessFlags) :*: S1 ('MetaSel ('Just "dstAccessMask") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 AccessFlags)))

data BufferMemoryBarrier Source #

VkBufferMemoryBarrier - Structure specifying a buffer memory barrier

Description

The first access scope is limited to access to memory through the specified buffer range, via access types in the source access mask specified by srcAccessMask. If srcAccessMask includes ACCESS_HOST_WRITE_BIT, memory writes performed by that access type are also made visible, as that access type is not performed through a resource.

The second access scope is limited to access to memory through the specified buffer range, via access types in the destination access mask specified by dstAccessMask. If dstAccessMask includes ACCESS_HOST_WRITE_BIT or ACCESS_HOST_READ_BIT, available memory writes are also made visible to accesses of those types, as those access types are not performed through a resource.

If srcQueueFamilyIndex is not equal to dstQueueFamilyIndex, and srcQueueFamilyIndex is equal to the current queue family, then the memory barrier defines a queue family release operation for the specified buffer range, and the second access scope includes no access, as if dstAccessMask was 0.

If dstQueueFamilyIndex is not equal to srcQueueFamilyIndex, and dstQueueFamilyIndex is equal to the current queue family, then the memory barrier defines a queue family acquire operation for the specified buffer range, and the first access scope includes no access, as if srcAccessMask was 0.

Valid Usage

  • offset must be less than the size of buffer

Valid Usage (Implicit)

  • pNext must be NULL
  • buffer must be a valid Buffer handle

See Also

AccessFlags, Buffer, DeviceSize, StructureType, cmdPipelineBarrier, cmdWaitEvents

Constructors

BufferMemoryBarrier 

Fields

Instances

Instances details
Eq BufferMemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Show BufferMemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Generic BufferMemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Associated Types

type Rep BufferMemoryBarrier :: Type -> Type #

Storable BufferMemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

FromCStruct BufferMemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

ToCStruct BufferMemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Zero BufferMemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

type Rep BufferMemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

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

VkImageMemoryBarrier - Structure specifying the parameters of an image memory barrier

Description

The first access scope is limited to access to memory through the specified image subresource range, via access types in the source access mask specified by srcAccessMask. If srcAccessMask includes ACCESS_HOST_WRITE_BIT, memory writes performed by that access type are also made visible, as that access type is not performed through a resource.

The second access scope is limited to access to memory through the specified image subresource range, via access types in the destination access mask specified by dstAccessMask. If dstAccessMask includes ACCESS_HOST_WRITE_BIT or ACCESS_HOST_READ_BIT, available memory writes are also made visible to accesses of those types, as those access types are not performed through a resource.

If srcQueueFamilyIndex is not equal to dstQueueFamilyIndex, and srcQueueFamilyIndex is equal to the current queue family, then the memory barrier defines a queue family release operation for the specified image subresource range, and the second access scope includes no access, as if dstAccessMask was 0.

If dstQueueFamilyIndex is not equal to srcQueueFamilyIndex, and dstQueueFamilyIndex is equal to the current queue family, then the memory barrier defines a queue family acquire operation for the specified image subresource range, and the first access scope includes no access, as if srcAccessMask was 0.

If oldLayout is not equal to newLayout, then the memory barrier defines an image layout transition for the specified image subresource range.

Layout transitions that are performed via image memory barriers execute in their entirety in submission order, relative to other image layout transitions submitted to the same queue, including those performed by render passes. In effect there is an implicit execution dependency from each such layout transition to all layout transitions previously submitted to the same queue.

The image layout of each image subresource of a depth/stencil image created with IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT is dependent on the last sample locations used to render to the image subresource as a depth/stencil attachment, thus when the image member of a ImageMemoryBarrier is an image created with this flag the application can include a SampleLocationsInfoEXT structure in the pNext chain of ImageMemoryBarrier to specify the sample locations to use during the image layout transition.

If the SampleLocationsInfoEXT structure included in the pNext chain of ImageMemoryBarrier does not match the sample location state last used to render to the image subresource range specified by subresourceRange or if no SampleLocationsInfoEXT structure is included in the pNext chain of ImageMemoryBarrier, then the contents of the given image subresource range becomes undefined as if oldLayout would equal IMAGE_LAYOUT_UNDEFINED.

If image has a multi-planar format and the image is disjoint, then including IMAGE_ASPECT_COLOR_BIT in the aspectMask member of subresourceRange is equivalent to including IMAGE_ASPECT_PLANE_0_BIT, IMAGE_ASPECT_PLANE_1_BIT, and (for three-plane formats only) IMAGE_ASPECT_PLANE_2_BIT.

Valid Usage

  • oldLayout must be IMAGE_LAYOUT_UNDEFINED or the current layout of the image subresources affected by the barrier

Valid Usage (Implicit)

See Also

AccessFlags, Image, ImageLayout, ImageSubresourceRange, StructureType, cmdPipelineBarrier, cmdWaitEvents

Constructors

ImageMemoryBarrier 

Fields

Instances

Instances details
Extensible ImageMemoryBarrier Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.OtherTypes

Generic (ImageMemoryBarrier es) Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Associated Types

type Rep (ImageMemoryBarrier es) :: Type -> Type #

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

Defined in Vulkan.Core10.OtherTypes

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

Defined in Vulkan.Core10.OtherTypes

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

Defined in Vulkan.Core10.OtherTypes

type Rep (ImageMemoryBarrier es) Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

data DrawIndirectCommand Source #

VkDrawIndirectCommand - Structure specifying a draw indirect command

Description

The members of DrawIndirectCommand have the same meaning as the similarly named parameters of cmdDraw.

Valid Usage

See Also

cmdDrawIndirect

Constructors

DrawIndirectCommand 

Fields

Instances

Instances details
Eq DrawIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Show DrawIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Generic DrawIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Associated Types

type Rep DrawIndirectCommand :: Type -> Type #

Storable DrawIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

FromCStruct DrawIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

ToCStruct DrawIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Zero DrawIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

type Rep DrawIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

type Rep DrawIndirectCommand = D1 ('MetaData "DrawIndirectCommand" "Vulkan.Core10.OtherTypes" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "DrawIndirectCommand" 'PrefixI 'True) ((S1 ('MetaSel ('Just "vertexCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "instanceCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "firstVertex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "firstInstance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32))))

data DrawIndexedIndirectCommand Source #

VkDrawIndexedIndirectCommand - Structure specifying a draw indexed indirect command

Description

The members of DrawIndexedIndirectCommand have the same meaning as the similarly named parameters of cmdDrawIndexed.

Valid Usage

  • (indexSize * (firstIndex + indexCount) + offset) must be less than or equal to the size of the bound index buffer, with indexSize being based on the type specified by indexType, where the index buffer, indexType, and offset are specified via cmdBindIndexBuffer
  • If the drawIndirectFirstInstance feature is not enabled, firstInstance must be 0

See Also

cmdDrawIndexedIndirect

Constructors

DrawIndexedIndirectCommand 

Fields

Instances

Instances details
Eq DrawIndexedIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Show DrawIndexedIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Generic DrawIndexedIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Associated Types

type Rep DrawIndexedIndirectCommand :: Type -> Type #

Storable DrawIndexedIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

FromCStruct DrawIndexedIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

ToCStruct DrawIndexedIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Zero DrawIndexedIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

type Rep DrawIndexedIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

type Rep DrawIndexedIndirectCommand = D1 ('MetaData "DrawIndexedIndirectCommand" "Vulkan.Core10.OtherTypes" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "DrawIndexedIndirectCommand" 'PrefixI 'True) ((S1 ('MetaSel ('Just "indexCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "instanceCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "firstIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "vertexOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int32) :*: S1 ('MetaSel ('Just "firstInstance") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)))))

data DispatchIndirectCommand Source #

VkDispatchIndirectCommand - Structure specifying a dispatch indirect command

Description

The members of DispatchIndirectCommand have the same meaning as the corresponding parameters of cmdDispatch.

Valid Usage

See Also

cmdDispatchIndirect

Constructors

DispatchIndirectCommand 

Fields

  • x :: Word32

    x is the number of local workgroups to dispatch in the X dimension.

    x must be less than or equal to PhysicalDeviceLimits::maxComputeWorkGroupCount[0]

  • y :: Word32

    y is the number of local workgroups to dispatch in the Y dimension.

    y must be less than or equal to PhysicalDeviceLimits::maxComputeWorkGroupCount[1]

  • z :: Word32

    z is the number of local workgroups to dispatch in the Z dimension.

    z must be less than or equal to PhysicalDeviceLimits::maxComputeWorkGroupCount[2]

Instances

Instances details
Eq DispatchIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Show DispatchIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Generic DispatchIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Associated Types

type Rep DispatchIndirectCommand :: Type -> Type #

Storable DispatchIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

FromCStruct DispatchIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

ToCStruct DispatchIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

Zero DispatchIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

type Rep DispatchIndirectCommand Source # 
Instance details

Defined in Vulkan.Core10.OtherTypes

type Rep DispatchIndirectCommand = D1 ('MetaData "DispatchIndirectCommand" "Vulkan.Core10.OtherTypes" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "DispatchIndirectCommand" 'PrefixI 'True) (S1 ('MetaSel ('Just "x") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "y") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "z") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32))))

data BaseOutStructure Source #

VkBaseOutStructure - Base structure for a read-only pointer chain

Description

BaseOutStructure can be used to facilitate iterating through a structure pointer chain that returns data back to the application.

See Also

BaseOutStructure, StructureType

Constructors

BaseOutStructure 

Fields

Instances

Instances details
Eq BaseOutStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

Show BaseOutStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

Generic BaseOutStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

Associated Types

type Rep BaseOutStructure :: Type -> Type #

Storable BaseOutStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

FromCStruct BaseOutStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

ToCStruct BaseOutStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

Zero BaseOutStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

type Rep BaseOutStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

type Rep BaseOutStructure = D1 ('MetaData "BaseOutStructure" "Vulkan.CStruct.Extends" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "BaseOutStructure" 'PrefixI 'True) (S1 ('MetaSel ('Just "sType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StructureType) :*: S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Ptr BaseOutStructure))))

data BaseInStructure Source #

VkBaseInStructure - Base structure for a read-only pointer chain

Description

BaseInStructure can be used to facilitate iterating through a read-only structure pointer chain.

See Also

BaseInStructure, StructureType

Constructors

BaseInStructure 

Fields

Instances

Instances details
Eq BaseInStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

Show BaseInStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

Generic BaseInStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

Associated Types

type Rep BaseInStructure :: Type -> Type #

Storable BaseInStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

FromCStruct BaseInStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

ToCStruct BaseInStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

Zero BaseInStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

type Rep BaseInStructure Source # 
Instance details

Defined in Vulkan.CStruct.Extends

type Rep BaseInStructure = D1 ('MetaData "BaseInStructure" "Vulkan.CStruct.Extends" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "BaseInStructure" 'PrefixI 'True) (S1 ('MetaSel ('Just "sType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 StructureType) :*: S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Ptr BaseInStructure))))

newtype ObjectType Source #

VkObjectType - Specify an enumeration to track object handle types

Description

'

ObjectType Vulkan Handle Type
OBJECT_TYPE_UNKNOWN Unknown/Undefined Handle
OBJECT_TYPE_INSTANCE Instance
OBJECT_TYPE_PHYSICAL_DEVICE PhysicalDevice
OBJECT_TYPE_DEVICE Device
OBJECT_TYPE_QUEUE Queue
OBJECT_TYPE_SEMAPHORE Semaphore
OBJECT_TYPE_COMMAND_BUFFER CommandBuffer
OBJECT_TYPE_FENCE Fence
OBJECT_TYPE_DEVICE_MEMORY DeviceMemory
OBJECT_TYPE_BUFFER Buffer
OBJECT_TYPE_IMAGE Image
OBJECT_TYPE_EVENT Event
OBJECT_TYPE_QUERY_POOL QueryPool
OBJECT_TYPE_BUFFER_VIEW BufferView
OBJECT_TYPE_IMAGE_VIEW ImageView
OBJECT_TYPE_SHADER_MODULE ShaderModule
OBJECT_TYPE_PIPELINE_CACHE PipelineCache
OBJECT_TYPE_PIPELINE_LAYOUT PipelineLayout
OBJECT_TYPE_RENDER_PASS RenderPass
OBJECT_TYPE_PIPELINE Pipeline
OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT DescriptorSetLayout
OBJECT_TYPE_SAMPLER Sampler
OBJECT_TYPE_DESCRIPTOR_POOL DescriptorPool
OBJECT_TYPE_DESCRIPTOR_SET DescriptorSet
OBJECT_TYPE_FRAMEBUFFER Framebuffer
OBJECT_TYPE_COMMAND_POOL CommandPool
OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION SamplerYcbcrConversion
OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE DescriptorUpdateTemplate
OBJECT_TYPE_SURFACE_KHR SurfaceKHR
OBJECT_TYPE_SWAPCHAIN_KHR SwapchainKHR
OBJECT_TYPE_DISPLAY_KHR DisplayKHR
OBJECT_TYPE_DISPLAY_MODE_KHR DisplayModeKHR
OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT DebugReportCallbackEXT
OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NV IndirectCommandsLayoutNV
OBJECT_TYPE_DEBUG_UTILS_MESSENGER_EXT DebugUtilsMessengerEXT
OBJECT_TYPE_VALIDATION_CACHE_EXT ValidationCacheEXT
OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR AccelerationStructureKHR
OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL PerformanceConfigurationINTEL

VkObjectType and Vulkan Handle Relationship

See Also

DebugUtilsObjectNameInfoEXT, DebugUtilsObjectTagInfoEXT, getPrivateDataEXT, setPrivateDataEXT

Constructors

ObjectType Int32 

Bundled Patterns

pattern OBJECT_TYPE_UNKNOWN :: ObjectType 
pattern OBJECT_TYPE_INSTANCE :: ObjectType 
pattern OBJECT_TYPE_PHYSICAL_DEVICE :: ObjectType 
pattern OBJECT_TYPE_DEVICE :: ObjectType 
pattern OBJECT_TYPE_QUEUE :: ObjectType 
pattern OBJECT_TYPE_SEMAPHORE :: ObjectType 
pattern OBJECT_TYPE_COMMAND_BUFFER :: ObjectType 
pattern OBJECT_TYPE_FENCE :: ObjectType 
pattern OBJECT_TYPE_DEVICE_MEMORY :: ObjectType 
pattern OBJECT_TYPE_BUFFER :: ObjectType 
pattern OBJECT_TYPE_IMAGE :: ObjectType 
pattern OBJECT_TYPE_EVENT :: ObjectType 
pattern OBJECT_TYPE_QUERY_POOL :: ObjectType 
pattern OBJECT_TYPE_BUFFER_VIEW :: ObjectType 
pattern OBJECT_TYPE_IMAGE_VIEW :: ObjectType 
pattern OBJECT_TYPE_SHADER_MODULE :: ObjectType 
pattern OBJECT_TYPE_PIPELINE_CACHE :: ObjectType 
pattern OBJECT_TYPE_PIPELINE_LAYOUT :: ObjectType 
pattern OBJECT_TYPE_RENDER_PASS :: ObjectType 
pattern OBJECT_TYPE_PIPELINE :: ObjectType 
pattern OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT :: ObjectType 
pattern OBJECT_TYPE_SAMPLER :: ObjectType 
pattern OBJECT_TYPE_DESCRIPTOR_POOL :: ObjectType 
pattern OBJECT_TYPE_DESCRIPTOR_SET :: ObjectType 
pattern OBJECT_TYPE_FRAMEBUFFER :: ObjectType 
pattern OBJECT_TYPE_COMMAND_POOL :: ObjectType 
pattern OBJECT_TYPE_PRIVATE_DATA_SLOT_EXT :: ObjectType 
pattern OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NV :: ObjectType 
pattern OBJECT_TYPE_DEFERRED_OPERATION_KHR :: ObjectType 
pattern OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL :: ObjectType 
pattern OBJECT_TYPE_VALIDATION_CACHE_EXT :: ObjectType 
pattern OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR :: ObjectType 
pattern OBJECT_TYPE_DEBUG_UTILS_MESSENGER_EXT :: ObjectType 
pattern OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT :: ObjectType 
pattern OBJECT_TYPE_DISPLAY_MODE_KHR :: ObjectType 
pattern OBJECT_TYPE_DISPLAY_KHR :: ObjectType 
pattern OBJECT_TYPE_SWAPCHAIN_KHR :: ObjectType 
pattern OBJECT_TYPE_SURFACE_KHR :: ObjectType 
pattern OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE :: ObjectType 
pattern OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION :: ObjectType 

Instances

Instances details
Eq ObjectType Source # 
Instance details

Defined in Vulkan.Core10.Enums.ObjectType

Ord ObjectType Source # 
Instance details

Defined in Vulkan.Core10.Enums.ObjectType

Read ObjectType Source # 
Instance details

Defined in Vulkan.Core10.Enums.ObjectType

Show ObjectType Source # 
Instance details

Defined in Vulkan.Core10.Enums.ObjectType

Storable ObjectType Source # 
Instance details

Defined in Vulkan.Core10.Enums.ObjectType

Zero ObjectType Source # 
Instance details

Defined in Vulkan.Core10.Enums.ObjectType

newtype VendorId Source #

VkVendorId - Khronos vendor IDs

Description

Note

Khronos vendor IDs may be allocated by vendors at any time. Only the latest canonical versions of this Specification, of the corresponding vk.xml API Registry, and of the corresponding vulkan_core.h header file must contain all reserved Khronos vendor IDs.

Only Khronos vendor IDs are given symbolic names at present. PCI vendor IDs returned by the implementation can be looked up in the PCI-SIG database.

See Also

No cross-references are available

Constructors

VendorId Int32 

Bundled Patterns

pattern VENDOR_ID_VIV :: VendorId 
pattern VENDOR_ID_VSI :: VendorId 
pattern VENDOR_ID_KAZAN :: VendorId 
pattern VENDOR_ID_CODEPLAY :: VendorId 
pattern VENDOR_ID_MESA :: VendorId 

Instances

Instances details
Eq VendorId Source # 
Instance details

Defined in Vulkan.Core10.Enums.VendorId

Ord VendorId Source # 
Instance details

Defined in Vulkan.Core10.Enums.VendorId

Read VendorId Source # 
Instance details

Defined in Vulkan.Core10.Enums.VendorId

Show VendorId Source # 
Instance details

Defined in Vulkan.Core10.Enums.VendorId

Storable VendorId Source # 
Instance details

Defined in Vulkan.Core10.Enums.VendorId

Zero VendorId Source # 
Instance details

Defined in Vulkan.Core10.Enums.VendorId

Methods

zero :: VendorId Source #