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

Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Synopsis

Documentation

createSamplerYcbcrConversion Source #

Arguments

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

device is the logical device that creates the sampler Y′CBCR conversion.

-> SamplerYcbcrConversionCreateInfo a

pCreateInfo is a pointer to a SamplerYcbcrConversionCreateInfo structure specifying the requested sampler Y′CBCR conversion.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io SamplerYcbcrConversion 

vkCreateSamplerYcbcrConversion - Create a new Y′CBCR conversion

Description

The interpretation of the configured sampler Y′CBCR conversion is described in more detail in the description of sampler Y′CBCR conversion in the Image Operations chapter.

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, SamplerYcbcrConversion, SamplerYcbcrConversionCreateInfo

withSamplerYcbcrConversion :: forall a io r. (Extendss SamplerYcbcrConversionCreateInfo a, PokeChain a, MonadIO io) => Device -> SamplerYcbcrConversionCreateInfo a -> Maybe AllocationCallbacks -> (io SamplerYcbcrConversion -> (SamplerYcbcrConversion -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createSamplerYcbcrConversion and destroySamplerYcbcrConversion

To ensure that destroySamplerYcbcrConversion is always called: pass bracket (or the allocate function from your favourite resource management library) as the first argument. To just extract the pair pass (,) as the first argument.

destroySamplerYcbcrConversion Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the Y′CBCR conversion.

-> SamplerYcbcrConversion

ycbcrConversion is the conversion to destroy.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io () 

vkDestroySamplerYcbcrConversion - Destroy a created Y′CBCR conversion

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If ycbcrConversion is not NULL_HANDLE, ycbcrConversion must be a valid SamplerYcbcrConversion handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • If ycbcrConversion is a valid handle, it must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to ycbcrConversion must be externally synchronized

See Also

AllocationCallbacks, Device, SamplerYcbcrConversion

data SamplerYcbcrConversionInfo Source #

VkSamplerYcbcrConversionInfo - Structure specifying Y′CBCR conversion to a sampler or image view

Valid Usage (Implicit)

See Also

SamplerYcbcrConversion, StructureType

Constructors

SamplerYcbcrConversionInfo 

Fields

Instances

Instances details
Eq SamplerYcbcrConversionInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Show SamplerYcbcrConversionInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Generic SamplerYcbcrConversionInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Associated Types

type Rep SamplerYcbcrConversionInfo :: Type -> Type #

Storable SamplerYcbcrConversionInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

FromCStruct SamplerYcbcrConversionInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

ToCStruct SamplerYcbcrConversionInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Zero SamplerYcbcrConversionInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep SamplerYcbcrConversionInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep SamplerYcbcrConversionInfo = D1 ('MetaData "SamplerYcbcrConversionInfo" "Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "SamplerYcbcrConversionInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "conversion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SamplerYcbcrConversion)))

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

VkSamplerYcbcrConversionCreateInfo - Structure specifying the parameters of the newly created conversion

Description

Note

Setting forceExplicitReconstruction to TRUE may have a performance penalty on implementations where explicit reconstruction is not the default mode of operation.

If format supports FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT the forceExplicitReconstruction value behaves as if it was set to TRUE.

If the pNext chain includes a ExternalFormatANDROID structure with non-zero externalFormat member, the sampler Y′CBCR conversion object represents an external format conversion, and format must be FORMAT_UNDEFINED. Such conversions must only be used to sample image views with a matching external format. When creating an external format conversion, the value of components is ignored.

Valid Usage

  • If an external format conversion is being created, format must be FORMAT_UNDEFINED

Valid Usage (Implicit)

If chromaFilter is FILTER_NEAREST, chroma samples are reconstructed to luma channel resolution using nearest-neighbour sampling. Otherwise, chroma samples are reconstructed using interpolation. More details can be found in the description of sampler Y′CBCR conversion in the Image Operations chapter.

See Also

Bool32, ChromaLocation, ComponentMapping, Filter, Format, SamplerYcbcrModelConversion, SamplerYcbcrRange, StructureType, createSamplerYcbcrConversion, createSamplerYcbcrConversionKHR

Constructors

SamplerYcbcrConversionCreateInfo 

Fields

Instances

Instances details
Extensible SamplerYcbcrConversionCreateInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

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

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Generic (SamplerYcbcrConversionCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Associated Types

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

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

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

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

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

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

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep (SamplerYcbcrConversionCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

data BindImagePlaneMemoryInfo Source #

VkBindImagePlaneMemoryInfo - Structure specifying how to bind an image plane to memory

Valid Usage

Valid Usage (Implicit)

See Also

ImageAspectFlagBits, StructureType

Constructors

BindImagePlaneMemoryInfo 

Fields

Instances

Instances details
Eq BindImagePlaneMemoryInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Show BindImagePlaneMemoryInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Generic BindImagePlaneMemoryInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Associated Types

type Rep BindImagePlaneMemoryInfo :: Type -> Type #

Storable BindImagePlaneMemoryInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

FromCStruct BindImagePlaneMemoryInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

ToCStruct BindImagePlaneMemoryInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Zero BindImagePlaneMemoryInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep BindImagePlaneMemoryInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep BindImagePlaneMemoryInfo = D1 ('MetaData "BindImagePlaneMemoryInfo" "Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "BindImagePlaneMemoryInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "planeAspect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageAspectFlagBits)))

data ImagePlaneMemoryRequirementsInfo Source #

VkImagePlaneMemoryRequirementsInfo - Structure specifying image plane for memory requirements

Valid Usage

Valid Usage (Implicit)

See Also

ImageAspectFlagBits, StructureType

Constructors

ImagePlaneMemoryRequirementsInfo 

Fields

Instances

Instances details
Eq ImagePlaneMemoryRequirementsInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Show ImagePlaneMemoryRequirementsInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Generic ImagePlaneMemoryRequirementsInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Associated Types

type Rep ImagePlaneMemoryRequirementsInfo :: Type -> Type #

Storable ImagePlaneMemoryRequirementsInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

FromCStruct ImagePlaneMemoryRequirementsInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

ToCStruct ImagePlaneMemoryRequirementsInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Zero ImagePlaneMemoryRequirementsInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep ImagePlaneMemoryRequirementsInfo Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep ImagePlaneMemoryRequirementsInfo = D1 ('MetaData "ImagePlaneMemoryRequirementsInfo" "Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "ImagePlaneMemoryRequirementsInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "planeAspect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageAspectFlagBits)))

data PhysicalDeviceSamplerYcbcrConversionFeatures Source #

VkPhysicalDeviceSamplerYcbcrConversionFeatures - Structure describing Y’CbCr conversion features that can be supported by an implementation

Members

The members of the PhysicalDeviceSamplerYcbcrConversionFeatures structure describe the following feature:

Valid Usage (Implicit)

See Also

Bool32, StructureType

Constructors

PhysicalDeviceSamplerYcbcrConversionFeatures 

Fields

Instances

Instances details
Eq PhysicalDeviceSamplerYcbcrConversionFeatures Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Show PhysicalDeviceSamplerYcbcrConversionFeatures Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Generic PhysicalDeviceSamplerYcbcrConversionFeatures Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Storable PhysicalDeviceSamplerYcbcrConversionFeatures Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

FromCStruct PhysicalDeviceSamplerYcbcrConversionFeatures Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

ToCStruct PhysicalDeviceSamplerYcbcrConversionFeatures Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Zero PhysicalDeviceSamplerYcbcrConversionFeatures Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep PhysicalDeviceSamplerYcbcrConversionFeatures Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep PhysicalDeviceSamplerYcbcrConversionFeatures = D1 ('MetaData "PhysicalDeviceSamplerYcbcrConversionFeatures" "Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "PhysicalDeviceSamplerYcbcrConversionFeatures" 'PrefixI 'True) (S1 ('MetaSel ('Just "samplerYcbcrConversion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))

data SamplerYcbcrConversionImageFormatProperties Source #

VkSamplerYcbcrConversionImageFormatProperties - Structure specifying combined image sampler descriptor count for multi-planar images

Valid Usage (Implicit)

See Also

StructureType

Constructors

SamplerYcbcrConversionImageFormatProperties 

Fields

Instances

Instances details
Eq SamplerYcbcrConversionImageFormatProperties Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Show SamplerYcbcrConversionImageFormatProperties Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Generic SamplerYcbcrConversionImageFormatProperties Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Storable SamplerYcbcrConversionImageFormatProperties Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

FromCStruct SamplerYcbcrConversionImageFormatProperties Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

ToCStruct SamplerYcbcrConversionImageFormatProperties Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

Zero SamplerYcbcrConversionImageFormatProperties Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep SamplerYcbcrConversionImageFormatProperties Source # 
Instance details

Defined in Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion

type Rep SamplerYcbcrConversionImageFormatProperties = D1 ('MetaData "SamplerYcbcrConversionImageFormatProperties" "Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "SamplerYcbcrConversionImageFormatProperties" 'PrefixI 'True) (S1 ('MetaSel ('Just "combinedImageSamplerDescriptorCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)))

newtype SamplerYcbcrConversion Source #

VkSamplerYcbcrConversion - Opaque handle to a device-specific sampler Y′CBCR conversion description

See Also

SamplerYcbcrConversionInfo, createSamplerYcbcrConversion, createSamplerYcbcrConversionKHR, destroySamplerYcbcrConversion, destroySamplerYcbcrConversionKHR

Instances

Instances details
Eq SamplerYcbcrConversion Source # 
Instance details

Defined in Vulkan.Core11.Handles

Ord SamplerYcbcrConversion Source # 
Instance details

Defined in Vulkan.Core11.Handles

Show SamplerYcbcrConversion Source # 
Instance details

Defined in Vulkan.Core11.Handles

Storable SamplerYcbcrConversion Source # 
Instance details

Defined in Vulkan.Core11.Handles

Zero SamplerYcbcrConversion Source # 
Instance details

Defined in Vulkan.Core11.Handles

HasObjectType SamplerYcbcrConversion Source # 
Instance details

Defined in Vulkan.Core11.Handles

IsHandle SamplerYcbcrConversion Source # 
Instance details

Defined in Vulkan.Core11.Handles

newtype Format Source #

Constructors

Format Int32 

Bundled Patterns

pattern FORMAT_UNDEFINED :: Format

FORMAT_UNDEFINED specifies that the format is not specified.

pattern FORMAT_R4G4_UNORM_PACK8 :: Format

FORMAT_R4G4_UNORM_PACK8 specifies a two-component, 8-bit packed unsigned normalized format that has a 4-bit R component in bits 4..7, and a 4-bit G component in bits 0..3.

pattern FORMAT_R4G4B4A4_UNORM_PACK16 :: Format

FORMAT_R4G4B4A4_UNORM_PACK16 specifies a four-component, 16-bit packed unsigned normalized format that has a 4-bit R component in bits 12..15, a 4-bit G component in bits 8..11, a 4-bit B component in bits 4..7, and a 4-bit A component in bits 0..3.

pattern FORMAT_B4G4R4A4_UNORM_PACK16 :: Format

FORMAT_B4G4R4A4_UNORM_PACK16 specifies a four-component, 16-bit packed unsigned normalized format that has a 4-bit B component in bits 12..15, a 4-bit G component in bits 8..11, a 4-bit R component in bits 4..7, and a 4-bit A component in bits 0..3.

pattern FORMAT_R5G6B5_UNORM_PACK16 :: Format

FORMAT_R5G6B5_UNORM_PACK16 specifies a three-component, 16-bit packed unsigned normalized format that has a 5-bit R component in bits 11..15, a 6-bit G component in bits 5..10, and a 5-bit B component in bits 0..4.

pattern FORMAT_B5G6R5_UNORM_PACK16 :: Format

FORMAT_B5G6R5_UNORM_PACK16 specifies a three-component, 16-bit packed unsigned normalized format that has a 5-bit B component in bits 11..15, a 6-bit G component in bits 5..10, and a 5-bit R component in bits 0..4.

pattern FORMAT_R5G5B5A1_UNORM_PACK16 :: Format

FORMAT_R5G5B5A1_UNORM_PACK16 specifies a four-component, 16-bit packed unsigned normalized format that has a 5-bit R component in bits 11..15, a 5-bit G component in bits 6..10, a 5-bit B component in bits 1..5, and a 1-bit A component in bit 0.

pattern FORMAT_B5G5R5A1_UNORM_PACK16 :: Format

FORMAT_B5G5R5A1_UNORM_PACK16 specifies a four-component, 16-bit packed unsigned normalized format that has a 5-bit B component in bits 11..15, a 5-bit G component in bits 6..10, a 5-bit R component in bits 1..5, and a 1-bit A component in bit 0.

pattern FORMAT_A1R5G5B5_UNORM_PACK16 :: Format

FORMAT_A1R5G5B5_UNORM_PACK16 specifies a four-component, 16-bit packed unsigned normalized format that has a 1-bit A component in bit 15, a 5-bit R component in bits 10..14, a 5-bit G component in bits 5..9, and a 5-bit B component in bits 0..4.

pattern FORMAT_R8_UNORM :: Format

FORMAT_R8_UNORM specifies a one-component, 8-bit unsigned normalized format that has a single 8-bit R component.

pattern FORMAT_R8_SNORM :: Format

FORMAT_R8_SNORM specifies a one-component, 8-bit signed normalized format that has a single 8-bit R component.

pattern FORMAT_R8_USCALED :: Format

FORMAT_R8_USCALED specifies a one-component, 8-bit unsigned scaled integer format that has a single 8-bit R component.

pattern FORMAT_R8_SSCALED :: Format

FORMAT_R8_SSCALED specifies a one-component, 8-bit signed scaled integer format that has a single 8-bit R component.

pattern FORMAT_R8_UINT :: Format

FORMAT_R8_UINT specifies a one-component, 8-bit unsigned integer format that has a single 8-bit R component.

pattern FORMAT_R8_SINT :: Format

FORMAT_R8_SINT specifies a one-component, 8-bit signed integer format that has a single 8-bit R component.

pattern FORMAT_R8_SRGB :: Format

FORMAT_R8_SRGB specifies a one-component, 8-bit unsigned normalized format that has a single 8-bit R component stored with sRGB nonlinear encoding.

pattern FORMAT_R8G8_UNORM :: Format

FORMAT_R8G8_UNORM specifies a two-component, 16-bit unsigned normalized format that has an 8-bit R component in byte 0, and an 8-bit G component in byte 1.

pattern FORMAT_R8G8_SNORM :: Format

FORMAT_R8G8_SNORM specifies a two-component, 16-bit signed normalized format that has an 8-bit R component in byte 0, and an 8-bit G component in byte 1.

pattern FORMAT_R8G8_USCALED :: Format

FORMAT_R8G8_USCALED specifies a two-component, 16-bit unsigned scaled integer format that has an 8-bit R component in byte 0, and an 8-bit G component in byte 1.

pattern FORMAT_R8G8_SSCALED :: Format

FORMAT_R8G8_SSCALED specifies a two-component, 16-bit signed scaled integer format that has an 8-bit R component in byte 0, and an 8-bit G component in byte 1.

pattern FORMAT_R8G8_UINT :: Format

FORMAT_R8G8_UINT specifies a two-component, 16-bit unsigned integer format that has an 8-bit R component in byte 0, and an 8-bit G component in byte 1.

pattern FORMAT_R8G8_SINT :: Format

FORMAT_R8G8_SINT specifies a two-component, 16-bit signed integer format that has an 8-bit R component in byte 0, and an 8-bit G component in byte 1.

pattern FORMAT_R8G8_SRGB :: Format

FORMAT_R8G8_SRGB specifies a two-component, 16-bit unsigned normalized format that has an 8-bit R component stored with sRGB nonlinear encoding in byte 0, and an 8-bit G component stored with sRGB nonlinear encoding in byte 1.

pattern FORMAT_R8G8B8_UNORM :: Format

FORMAT_R8G8B8_UNORM specifies a three-component, 24-bit unsigned normalized format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, and an 8-bit B component in byte 2.

pattern FORMAT_R8G8B8_SNORM :: Format

FORMAT_R8G8B8_SNORM specifies a three-component, 24-bit signed normalized format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, and an 8-bit B component in byte 2.

pattern FORMAT_R8G8B8_USCALED :: Format

FORMAT_R8G8B8_USCALED specifies a three-component, 24-bit unsigned scaled format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, and an 8-bit B component in byte 2.

pattern FORMAT_R8G8B8_SSCALED :: Format

FORMAT_R8G8B8_SSCALED specifies a three-component, 24-bit signed scaled format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, and an 8-bit B component in byte 2.

pattern FORMAT_R8G8B8_UINT :: Format

FORMAT_R8G8B8_UINT specifies a three-component, 24-bit unsigned integer format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, and an 8-bit B component in byte 2.

pattern FORMAT_R8G8B8_SINT :: Format

FORMAT_R8G8B8_SINT specifies a three-component, 24-bit signed integer format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, and an 8-bit B component in byte 2.

pattern FORMAT_R8G8B8_SRGB :: Format

FORMAT_R8G8B8_SRGB specifies a three-component, 24-bit unsigned normalized format that has an 8-bit R component stored with sRGB nonlinear encoding in byte 0, an 8-bit G component stored with sRGB nonlinear encoding in byte 1, and an 8-bit B component stored with sRGB nonlinear encoding in byte 2.

pattern FORMAT_B8G8R8_UNORM :: Format

FORMAT_B8G8R8_UNORM specifies a three-component, 24-bit unsigned normalized format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, and an 8-bit R component in byte 2.

pattern FORMAT_B8G8R8_SNORM :: Format

FORMAT_B8G8R8_SNORM specifies a three-component, 24-bit signed normalized format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, and an 8-bit R component in byte 2.

pattern FORMAT_B8G8R8_USCALED :: Format

FORMAT_B8G8R8_USCALED specifies a three-component, 24-bit unsigned scaled format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, and an 8-bit R component in byte 2.

pattern FORMAT_B8G8R8_SSCALED :: Format

FORMAT_B8G8R8_SSCALED specifies a three-component, 24-bit signed scaled format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, and an 8-bit R component in byte 2.

pattern FORMAT_B8G8R8_UINT :: Format

FORMAT_B8G8R8_UINT specifies a three-component, 24-bit unsigned integer format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, and an 8-bit R component in byte 2.

pattern FORMAT_B8G8R8_SINT :: Format

FORMAT_B8G8R8_SINT specifies a three-component, 24-bit signed integer format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, and an 8-bit R component in byte 2.

pattern FORMAT_B8G8R8_SRGB :: Format

FORMAT_B8G8R8_SRGB specifies a three-component, 24-bit unsigned normalized format that has an 8-bit B component stored with sRGB nonlinear encoding in byte 0, an 8-bit G component stored with sRGB nonlinear encoding in byte 1, and an 8-bit R component stored with sRGB nonlinear encoding in byte 2.

pattern FORMAT_R8G8B8A8_UNORM :: Format

FORMAT_R8G8B8A8_UNORM specifies a four-component, 32-bit unsigned normalized format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, an 8-bit B component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_R8G8B8A8_SNORM :: Format

FORMAT_R8G8B8A8_SNORM specifies a four-component, 32-bit signed normalized format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, an 8-bit B component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_R8G8B8A8_USCALED :: Format

FORMAT_R8G8B8A8_USCALED specifies a four-component, 32-bit unsigned scaled format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, an 8-bit B component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_R8G8B8A8_SSCALED :: Format

FORMAT_R8G8B8A8_SSCALED specifies a four-component, 32-bit signed scaled format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, an 8-bit B component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_R8G8B8A8_UINT :: Format

FORMAT_R8G8B8A8_UINT specifies a four-component, 32-bit unsigned integer format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, an 8-bit B component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_R8G8B8A8_SINT :: Format

FORMAT_R8G8B8A8_SINT specifies a four-component, 32-bit signed integer format that has an 8-bit R component in byte 0, an 8-bit G component in byte 1, an 8-bit B component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_R8G8B8A8_SRGB :: Format

FORMAT_R8G8B8A8_SRGB specifies a four-component, 32-bit unsigned normalized format that has an 8-bit R component stored with sRGB nonlinear encoding in byte 0, an 8-bit G component stored with sRGB nonlinear encoding in byte 1, an 8-bit B component stored with sRGB nonlinear encoding in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_B8G8R8A8_UNORM :: Format

FORMAT_B8G8R8A8_UNORM specifies a four-component, 32-bit unsigned normalized format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, an 8-bit R component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_B8G8R8A8_SNORM :: Format

FORMAT_B8G8R8A8_SNORM specifies a four-component, 32-bit signed normalized format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, an 8-bit R component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_B8G8R8A8_USCALED :: Format

FORMAT_B8G8R8A8_USCALED specifies a four-component, 32-bit unsigned scaled format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, an 8-bit R component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_B8G8R8A8_SSCALED :: Format

FORMAT_B8G8R8A8_SSCALED specifies a four-component, 32-bit signed scaled format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, an 8-bit R component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_B8G8R8A8_UINT :: Format

FORMAT_B8G8R8A8_UINT specifies a four-component, 32-bit unsigned integer format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, an 8-bit R component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_B8G8R8A8_SINT :: Format

FORMAT_B8G8R8A8_SINT specifies a four-component, 32-bit signed integer format that has an 8-bit B component in byte 0, an 8-bit G component in byte 1, an 8-bit R component in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_B8G8R8A8_SRGB :: Format

FORMAT_B8G8R8A8_SRGB specifies a four-component, 32-bit unsigned normalized format that has an 8-bit B component stored with sRGB nonlinear encoding in byte 0, an 8-bit G component stored with sRGB nonlinear encoding in byte 1, an 8-bit R component stored with sRGB nonlinear encoding in byte 2, and an 8-bit A component in byte 3.

pattern FORMAT_A8B8G8R8_UNORM_PACK32 :: Format

FORMAT_A8B8G8R8_UNORM_PACK32 specifies a four-component, 32-bit packed unsigned normalized format that has an 8-bit A component in bits 24..31, an 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15, and an 8-bit R component in bits 0..7.

pattern FORMAT_A8B8G8R8_SNORM_PACK32 :: Format

FORMAT_A8B8G8R8_SNORM_PACK32 specifies a four-component, 32-bit packed signed normalized format that has an 8-bit A component in bits 24..31, an 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15, and an 8-bit R component in bits 0..7.

pattern FORMAT_A8B8G8R8_USCALED_PACK32 :: Format

FORMAT_A8B8G8R8_USCALED_PACK32 specifies a four-component, 32-bit packed unsigned scaled integer format that has an 8-bit A component in bits 24..31, an 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15, and an 8-bit R component in bits 0..7.

pattern FORMAT_A8B8G8R8_SSCALED_PACK32 :: Format

FORMAT_A8B8G8R8_SSCALED_PACK32 specifies a four-component, 32-bit packed signed scaled integer format that has an 8-bit A component in bits 24..31, an 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15, and an 8-bit R component in bits 0..7.

pattern FORMAT_A8B8G8R8_UINT_PACK32 :: Format

FORMAT_A8B8G8R8_UINT_PACK32 specifies a four-component, 32-bit packed unsigned integer format that has an 8-bit A component in bits 24..31, an 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15, and an 8-bit R component in bits 0..7.

pattern FORMAT_A8B8G8R8_SINT_PACK32 :: Format

FORMAT_A8B8G8R8_SINT_PACK32 specifies a four-component, 32-bit packed signed integer format that has an 8-bit A component in bits 24..31, an 8-bit B component in bits 16..23, an 8-bit G component in bits 8..15, and an 8-bit R component in bits 0..7.

pattern FORMAT_A8B8G8R8_SRGB_PACK32 :: Format

FORMAT_A8B8G8R8_SRGB_PACK32 specifies a four-component, 32-bit packed unsigned normalized format that has an 8-bit A component in bits 24..31, an 8-bit B component stored with sRGB nonlinear encoding in bits 16..23, an 8-bit G component stored with sRGB nonlinear encoding in bits 8..15, and an 8-bit R component stored with sRGB nonlinear encoding in bits 0..7.

pattern FORMAT_A2R10G10B10_UNORM_PACK32 :: Format

FORMAT_A2R10G10B10_UNORM_PACK32 specifies a four-component, 32-bit packed unsigned normalized format that has a 2-bit A component in bits 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit B component in bits 0..9.

pattern FORMAT_A2R10G10B10_SNORM_PACK32 :: Format

FORMAT_A2R10G10B10_SNORM_PACK32 specifies a four-component, 32-bit packed signed normalized format that has a 2-bit A component in bits 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit B component in bits 0..9.

pattern FORMAT_A2R10G10B10_USCALED_PACK32 :: Format

FORMAT_A2R10G10B10_USCALED_PACK32 specifies a four-component, 32-bit packed unsigned scaled integer format that has a 2-bit A component in bits 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit B component in bits 0..9.

pattern FORMAT_A2R10G10B10_SSCALED_PACK32 :: Format

FORMAT_A2R10G10B10_SSCALED_PACK32 specifies a four-component, 32-bit packed signed scaled integer format that has a 2-bit A component in bits 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit B component in bits 0..9.

pattern FORMAT_A2R10G10B10_UINT_PACK32 :: Format

FORMAT_A2R10G10B10_UINT_PACK32 specifies a four-component, 32-bit packed unsigned integer format that has a 2-bit A component in bits 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit B component in bits 0..9.

pattern FORMAT_A2R10G10B10_SINT_PACK32 :: Format

FORMAT_A2R10G10B10_SINT_PACK32 specifies a four-component, 32-bit packed signed integer format that has a 2-bit A component in bits 30..31, a 10-bit R component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit B component in bits 0..9.

pattern FORMAT_A2B10G10R10_UNORM_PACK32 :: Format

FORMAT_A2B10G10R10_UNORM_PACK32 specifies a four-component, 32-bit packed unsigned normalized format that has a 2-bit A component in bits 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit R component in bits 0..9.

pattern FORMAT_A2B10G10R10_SNORM_PACK32 :: Format

FORMAT_A2B10G10R10_SNORM_PACK32 specifies a four-component, 32-bit packed signed normalized format that has a 2-bit A component in bits 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit R component in bits 0..9.

pattern FORMAT_A2B10G10R10_USCALED_PACK32 :: Format

FORMAT_A2B10G10R10_USCALED_PACK32 specifies a four-component, 32-bit packed unsigned scaled integer format that has a 2-bit A component in bits 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit R component in bits 0..9.

pattern FORMAT_A2B10G10R10_SSCALED_PACK32 :: Format

FORMAT_A2B10G10R10_SSCALED_PACK32 specifies a four-component, 32-bit packed signed scaled integer format that has a 2-bit A component in bits 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit R component in bits 0..9.

pattern FORMAT_A2B10G10R10_UINT_PACK32 :: Format

FORMAT_A2B10G10R10_UINT_PACK32 specifies a four-component, 32-bit packed unsigned integer format that has a 2-bit A component in bits 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit R component in bits 0..9.

pattern FORMAT_A2B10G10R10_SINT_PACK32 :: Format

FORMAT_A2B10G10R10_SINT_PACK32 specifies a four-component, 32-bit packed signed integer format that has a 2-bit A component in bits 30..31, a 10-bit B component in bits 20..29, a 10-bit G component in bits 10..19, and a 10-bit R component in bits 0..9.

pattern FORMAT_R16_UNORM :: Format

FORMAT_R16_UNORM specifies a one-component, 16-bit unsigned normalized format that has a single 16-bit R component.

pattern FORMAT_R16_SNORM :: Format

FORMAT_R16_SNORM specifies a one-component, 16-bit signed normalized format that has a single 16-bit R component.

pattern FORMAT_R16_USCALED :: Format

FORMAT_R16_USCALED specifies a one-component, 16-bit unsigned scaled integer format that has a single 16-bit R component.

pattern FORMAT_R16_SSCALED :: Format

FORMAT_R16_SSCALED specifies a one-component, 16-bit signed scaled integer format that has a single 16-bit R component.

pattern FORMAT_R16_UINT :: Format

FORMAT_R16_UINT specifies a one-component, 16-bit unsigned integer format that has a single 16-bit R component.

pattern FORMAT_R16_SINT :: Format

FORMAT_R16_SINT specifies a one-component, 16-bit signed integer format that has a single 16-bit R component.

pattern FORMAT_R16_SFLOAT :: Format

FORMAT_R16_SFLOAT specifies a one-component, 16-bit signed floating-point format that has a single 16-bit R component.

pattern FORMAT_R16G16_UNORM :: Format

FORMAT_R16G16_UNORM specifies a two-component, 32-bit unsigned normalized format that has a 16-bit R component in bytes 0..1, and a 16-bit G component in bytes 2..3.

pattern FORMAT_R16G16_SNORM :: Format

FORMAT_R16G16_SNORM specifies a two-component, 32-bit signed normalized format that has a 16-bit R component in bytes 0..1, and a 16-bit G component in bytes 2..3.

pattern FORMAT_R16G16_USCALED :: Format

FORMAT_R16G16_USCALED specifies a two-component, 32-bit unsigned scaled integer format that has a 16-bit R component in bytes 0..1, and a 16-bit G component in bytes 2..3.

pattern FORMAT_R16G16_SSCALED :: Format

FORMAT_R16G16_SSCALED specifies a two-component, 32-bit signed scaled integer format that has a 16-bit R component in bytes 0..1, and a 16-bit G component in bytes 2..3.

pattern FORMAT_R16G16_UINT :: Format

FORMAT_R16G16_UINT specifies a two-component, 32-bit unsigned integer format that has a 16-bit R component in bytes 0..1, and a 16-bit G component in bytes 2..3.

pattern FORMAT_R16G16_SINT :: Format

FORMAT_R16G16_SINT specifies a two-component, 32-bit signed integer format that has a 16-bit R component in bytes 0..1, and a 16-bit G component in bytes 2..3.

pattern FORMAT_R16G16_SFLOAT :: Format

FORMAT_R16G16_SFLOAT specifies a two-component, 32-bit signed floating-point format that has a 16-bit R component in bytes 0..1, and a 16-bit G component in bytes 2..3.

pattern FORMAT_R16G16B16_UNORM :: Format

FORMAT_R16G16B16_UNORM specifies a three-component, 48-bit unsigned normalized format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, and a 16-bit B component in bytes 4..5.

pattern FORMAT_R16G16B16_SNORM :: Format

FORMAT_R16G16B16_SNORM specifies a three-component, 48-bit signed normalized format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, and a 16-bit B component in bytes 4..5.

pattern FORMAT_R16G16B16_USCALED :: Format

FORMAT_R16G16B16_USCALED specifies a three-component, 48-bit unsigned scaled integer format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, and a 16-bit B component in bytes 4..5.

pattern FORMAT_R16G16B16_SSCALED :: Format

FORMAT_R16G16B16_SSCALED specifies a three-component, 48-bit signed scaled integer format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, and a 16-bit B component in bytes 4..5.

pattern FORMAT_R16G16B16_UINT :: Format

FORMAT_R16G16B16_UINT specifies a three-component, 48-bit unsigned integer format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, and a 16-bit B component in bytes 4..5.

pattern FORMAT_R16G16B16_SINT :: Format

FORMAT_R16G16B16_SINT specifies a three-component, 48-bit signed integer format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, and a 16-bit B component in bytes 4..5.

pattern FORMAT_R16G16B16_SFLOAT :: Format

FORMAT_R16G16B16_SFLOAT specifies a three-component, 48-bit signed floating-point format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, and a 16-bit B component in bytes 4..5.

pattern FORMAT_R16G16B16A16_UNORM :: Format

FORMAT_R16G16B16A16_UNORM specifies a four-component, 64-bit unsigned normalized format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, a 16-bit B component in bytes 4..5, and a 16-bit A component in bytes 6..7.

pattern FORMAT_R16G16B16A16_SNORM :: Format

FORMAT_R16G16B16A16_SNORM specifies a four-component, 64-bit signed normalized format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, a 16-bit B component in bytes 4..5, and a 16-bit A component in bytes 6..7.

pattern FORMAT_R16G16B16A16_USCALED :: Format

FORMAT_R16G16B16A16_USCALED specifies a four-component, 64-bit unsigned scaled integer format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, a 16-bit B component in bytes 4..5, and a 16-bit A component in bytes 6..7.

pattern FORMAT_R16G16B16A16_SSCALED :: Format

FORMAT_R16G16B16A16_SSCALED specifies a four-component, 64-bit signed scaled integer format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, a 16-bit B component in bytes 4..5, and a 16-bit A component in bytes 6..7.

pattern FORMAT_R16G16B16A16_UINT :: Format

FORMAT_R16G16B16A16_UINT specifies a four-component, 64-bit unsigned integer format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, a 16-bit B component in bytes 4..5, and a 16-bit A component in bytes 6..7.

pattern FORMAT_R16G16B16A16_SINT :: Format

FORMAT_R16G16B16A16_SINT specifies a four-component, 64-bit signed integer format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, a 16-bit B component in bytes 4..5, and a 16-bit A component in bytes 6..7.

pattern FORMAT_R16G16B16A16_SFLOAT :: Format

FORMAT_R16G16B16A16_SFLOAT specifies a four-component, 64-bit signed floating-point format that has a 16-bit R component in bytes 0..1, a 16-bit G component in bytes 2..3, a 16-bit B component in bytes 4..5, and a 16-bit A component in bytes 6..7.

pattern FORMAT_R32_UINT :: Format

FORMAT_R32_UINT specifies a one-component, 32-bit unsigned integer format that has a single 32-bit R component.

pattern FORMAT_R32_SINT :: Format

FORMAT_R32_SINT specifies a one-component, 32-bit signed integer format that has a single 32-bit R component.

pattern FORMAT_R32_SFLOAT :: Format

FORMAT_R32_SFLOAT specifies a one-component, 32-bit signed floating-point format that has a single 32-bit R component.

pattern FORMAT_R32G32_UINT :: Format

FORMAT_R32G32_UINT specifies a two-component, 64-bit unsigned integer format that has a 32-bit R component in bytes 0..3, and a 32-bit G component in bytes 4..7.

pattern FORMAT_R32G32_SINT :: Format

FORMAT_R32G32_SINT specifies a two-component, 64-bit signed integer format that has a 32-bit R component in bytes 0..3, and a 32-bit G component in bytes 4..7.

pattern FORMAT_R32G32_SFLOAT :: Format

FORMAT_R32G32_SFLOAT specifies a two-component, 64-bit signed floating-point format that has a 32-bit R component in bytes 0..3, and a 32-bit G component in bytes 4..7.

pattern FORMAT_R32G32B32_UINT :: Format

FORMAT_R32G32B32_UINT specifies a three-component, 96-bit unsigned integer format that has a 32-bit R component in bytes 0..3, a 32-bit G component in bytes 4..7, and a 32-bit B component in bytes 8..11.

pattern FORMAT_R32G32B32_SINT :: Format

FORMAT_R32G32B32_SINT specifies a three-component, 96-bit signed integer format that has a 32-bit R component in bytes 0..3, a 32-bit G component in bytes 4..7, and a 32-bit B component in bytes 8..11.

pattern FORMAT_R32G32B32_SFLOAT :: Format

FORMAT_R32G32B32_SFLOAT specifies a three-component, 96-bit signed floating-point format that has a 32-bit R component in bytes 0..3, a 32-bit G component in bytes 4..7, and a 32-bit B component in bytes 8..11.

pattern FORMAT_R32G32B32A32_UINT :: Format

FORMAT_R32G32B32A32_UINT specifies a four-component, 128-bit unsigned integer format that has a 32-bit R component in bytes 0..3, a 32-bit G component in bytes 4..7, a 32-bit B component in bytes 8..11, and a 32-bit A component in bytes 12..15.

pattern FORMAT_R32G32B32A32_SINT :: Format

FORMAT_R32G32B32A32_SINT specifies a four-component, 128-bit signed integer format that has a 32-bit R component in bytes 0..3, a 32-bit G component in bytes 4..7, a 32-bit B component in bytes 8..11, and a 32-bit A component in bytes 12..15.

pattern FORMAT_R32G32B32A32_SFLOAT :: Format

FORMAT_R32G32B32A32_SFLOAT specifies a four-component, 128-bit signed floating-point format that has a 32-bit R component in bytes 0..3, a 32-bit G component in bytes 4..7, a 32-bit B component in bytes 8..11, and a 32-bit A component in bytes 12..15.

pattern FORMAT_R64_UINT :: Format

FORMAT_R64_UINT specifies a one-component, 64-bit unsigned integer format that has a single 64-bit R component.

pattern FORMAT_R64_SINT :: Format

FORMAT_R64_SINT specifies a one-component, 64-bit signed integer format that has a single 64-bit R component.

pattern FORMAT_R64_SFLOAT :: Format

FORMAT_R64_SFLOAT specifies a one-component, 64-bit signed floating-point format that has a single 64-bit R component.

pattern FORMAT_R64G64_UINT :: Format

FORMAT_R64G64_UINT specifies a two-component, 128-bit unsigned integer format that has a 64-bit R component in bytes 0..7, and a 64-bit G component in bytes 8..15.

pattern FORMAT_R64G64_SINT :: Format

FORMAT_R64G64_SINT specifies a two-component, 128-bit signed integer format that has a 64-bit R component in bytes 0..7, and a 64-bit G component in bytes 8..15.

pattern FORMAT_R64G64_SFLOAT :: Format

FORMAT_R64G64_SFLOAT specifies a two-component, 128-bit signed floating-point format that has a 64-bit R component in bytes 0..7, and a 64-bit G component in bytes 8..15.

pattern FORMAT_R64G64B64_UINT :: Format

FORMAT_R64G64B64_UINT specifies a three-component, 192-bit unsigned integer format that has a 64-bit R component in bytes 0..7, a 64-bit G component in bytes 8..15, and a 64-bit B component in bytes 16..23.

pattern FORMAT_R64G64B64_SINT :: Format

FORMAT_R64G64B64_SINT specifies a three-component, 192-bit signed integer format that has a 64-bit R component in bytes 0..7, a 64-bit G component in bytes 8..15, and a 64-bit B component in bytes 16..23.

pattern FORMAT_R64G64B64_SFLOAT :: Format

FORMAT_R64G64B64_SFLOAT specifies a three-component, 192-bit signed floating-point format that has a 64-bit R component in bytes 0..7, a 64-bit G component in bytes 8..15, and a 64-bit B component in bytes 16..23.

pattern FORMAT_R64G64B64A64_UINT :: Format

FORMAT_R64G64B64A64_UINT specifies a four-component, 256-bit unsigned integer format that has a 64-bit R component in bytes 0..7, a 64-bit G component in bytes 8..15, a 64-bit B component in bytes 16..23, and a 64-bit A component in bytes 24..31.

pattern FORMAT_R64G64B64A64_SINT :: Format

FORMAT_R64G64B64A64_SINT specifies a four-component, 256-bit signed integer format that has a 64-bit R component in bytes 0..7, a 64-bit G component in bytes 8..15, a 64-bit B component in bytes 16..23, and a 64-bit A component in bytes 24..31.

pattern FORMAT_R64G64B64A64_SFLOAT :: Format

FORMAT_R64G64B64A64_SFLOAT specifies a four-component, 256-bit signed floating-point format that has a 64-bit R component in bytes 0..7, a 64-bit G component in bytes 8..15, a 64-bit B component in bytes 16..23, and a 64-bit A component in bytes 24..31.

pattern FORMAT_B10G11R11_UFLOAT_PACK32 :: Format

FORMAT_B10G11R11_UFLOAT_PACK32 specifies a three-component, 32-bit packed unsigned floating-point format that has a 10-bit B component in bits 22..31, an 11-bit G component in bits 11..21, an 11-bit R component in bits 0..10. See https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-fp10 and https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-fp11.

pattern FORMAT_E5B9G9R9_UFLOAT_PACK32 :: Format

FORMAT_E5B9G9R9_UFLOAT_PACK32 specifies a three-component, 32-bit packed unsigned floating-point format that has a 5-bit shared exponent in bits 27..31, a 9-bit B component mantissa in bits 18..26, a 9-bit G component mantissa in bits 9..17, and a 9-bit R component mantissa in bits 0..8.

pattern FORMAT_D16_UNORM :: Format

FORMAT_D16_UNORM specifies a one-component, 16-bit unsigned normalized format that has a single 16-bit depth component.

pattern FORMAT_X8_D24_UNORM_PACK32 :: Format

FORMAT_X8_D24_UNORM_PACK32 specifies a two-component, 32-bit format that has 24 unsigned normalized bits in the depth component and, optionally:, 8 bits that are unused.

pattern FORMAT_D32_SFLOAT :: Format

FORMAT_D32_SFLOAT specifies a one-component, 32-bit signed floating-point format that has 32-bits in the depth component.

pattern FORMAT_S8_UINT :: Format

FORMAT_S8_UINT specifies a one-component, 8-bit unsigned integer format that has 8-bits in the stencil component.

pattern FORMAT_D16_UNORM_S8_UINT :: Format

FORMAT_D16_UNORM_S8_UINT specifies a two-component, 24-bit format that has 16 unsigned normalized bits in the depth component and 8 unsigned integer bits in the stencil component.

pattern FORMAT_D24_UNORM_S8_UINT :: Format

FORMAT_D24_UNORM_S8_UINT specifies a two-component, 32-bit packed format that has 8 unsigned integer bits in the stencil component, and 24 unsigned normalized bits in the depth component.

pattern FORMAT_D32_SFLOAT_S8_UINT :: Format

FORMAT_D32_SFLOAT_S8_UINT specifies a two-component format that has 32 signed float bits in the depth component and 8 unsigned integer bits in the stencil component. There are optionally: 24-bits that are unused.

pattern FORMAT_BC1_RGB_UNORM_BLOCK :: Format

FORMAT_BC1_RGB_UNORM_BLOCK specifies a three-component, block-compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGB texel data. This format has no alpha and is considered opaque.

pattern FORMAT_BC1_RGB_SRGB_BLOCK :: Format

FORMAT_BC1_RGB_SRGB_BLOCK specifies a three-component, block-compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGB texel data with sRGB nonlinear encoding. This format has no alpha and is considered opaque.

pattern FORMAT_BC1_RGBA_UNORM_BLOCK :: Format

FORMAT_BC1_RGBA_UNORM_BLOCK specifies a four-component, block-compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGB texel data, and provides 1 bit of alpha.

pattern FORMAT_BC1_RGBA_SRGB_BLOCK :: Format

FORMAT_BC1_RGBA_SRGB_BLOCK specifies a four-component, block-compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGB texel data with sRGB nonlinear encoding, and provides 1 bit of alpha.

pattern FORMAT_BC2_UNORM_BLOCK :: Format

FORMAT_BC2_UNORM_BLOCK specifies a four-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with the first 64 bits encoding alpha values followed by 64 bits encoding RGB values.

pattern FORMAT_BC2_SRGB_BLOCK :: Format

FORMAT_BC2_SRGB_BLOCK specifies a four-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with the first 64 bits encoding alpha values followed by 64 bits encoding RGB values with sRGB nonlinear encoding.

pattern FORMAT_BC3_UNORM_BLOCK :: Format

FORMAT_BC3_UNORM_BLOCK specifies a four-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with the first 64 bits encoding alpha values followed by 64 bits encoding RGB values.

pattern FORMAT_BC3_SRGB_BLOCK :: Format

FORMAT_BC3_SRGB_BLOCK specifies a four-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with the first 64 bits encoding alpha values followed by 64 bits encoding RGB values with sRGB nonlinear encoding.

pattern FORMAT_BC4_UNORM_BLOCK :: Format

FORMAT_BC4_UNORM_BLOCK specifies a one-component, block-compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized red texel data.

pattern FORMAT_BC4_SNORM_BLOCK :: Format

FORMAT_BC4_SNORM_BLOCK specifies a one-component, block-compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of signed normalized red texel data.

pattern FORMAT_BC5_UNORM_BLOCK :: Format

FORMAT_BC5_UNORM_BLOCK specifies a two-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RG texel data with the first 64 bits encoding red values followed by 64 bits encoding green values.

pattern FORMAT_BC5_SNORM_BLOCK :: Format

FORMAT_BC5_SNORM_BLOCK specifies a two-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of signed normalized RG texel data with the first 64 bits encoding red values followed by 64 bits encoding green values.

pattern FORMAT_BC6H_UFLOAT_BLOCK :: Format

FORMAT_BC6H_UFLOAT_BLOCK specifies a three-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned floating-point RGB texel data.

pattern FORMAT_BC6H_SFLOAT_BLOCK :: Format

FORMAT_BC6H_SFLOAT_BLOCK specifies a three-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of signed floating-point RGB texel data.

pattern FORMAT_BC7_UNORM_BLOCK :: Format

FORMAT_BC7_UNORM_BLOCK specifies a four-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_BC7_SRGB_BLOCK :: Format

FORMAT_BC7_SRGB_BLOCK specifies a four-component, block-compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ETC2_R8G8B8_UNORM_BLOCK :: Format

FORMAT_ETC2_R8G8B8_UNORM_BLOCK specifies a three-component, ETC2 compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGB texel data. This format has no alpha and is considered opaque.

pattern FORMAT_ETC2_R8G8B8_SRGB_BLOCK :: Format

FORMAT_ETC2_R8G8B8_SRGB_BLOCK specifies a three-component, ETC2 compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGB texel data with sRGB nonlinear encoding. This format has no alpha and is considered opaque.

pattern FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK :: Format

FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK specifies a four-component, ETC2 compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGB texel data, and provides 1 bit of alpha.

pattern FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK :: Format

FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK specifies a four-component, ETC2 compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGB texel data with sRGB nonlinear encoding, and provides 1 bit of alpha.

pattern FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK :: Format

FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK specifies a four-component, ETC2 compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with the first 64 bits encoding alpha values followed by 64 bits encoding RGB values.

pattern FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK :: Format

FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK specifies a four-component, ETC2 compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with the first 64 bits encoding alpha values followed by 64 bits encoding RGB values with sRGB nonlinear encoding applied.

pattern FORMAT_EAC_R11_UNORM_BLOCK :: Format

FORMAT_EAC_R11_UNORM_BLOCK specifies a one-component, ETC2 compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized red texel data.

pattern FORMAT_EAC_R11_SNORM_BLOCK :: Format

FORMAT_EAC_R11_SNORM_BLOCK specifies a one-component, ETC2 compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of signed normalized red texel data.

pattern FORMAT_EAC_R11G11_UNORM_BLOCK :: Format

FORMAT_EAC_R11G11_UNORM_BLOCK specifies a two-component, ETC2 compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RG texel data with the first 64 bits encoding red values followed by 64 bits encoding green values.

pattern FORMAT_EAC_R11G11_SNORM_BLOCK :: Format

FORMAT_EAC_R11G11_SNORM_BLOCK specifies a two-component, ETC2 compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of signed normalized RG texel data with the first 64 bits encoding red values followed by 64 bits encoding green values.

pattern FORMAT_ASTC_4x4_UNORM_BLOCK :: Format

FORMAT_ASTC_4x4_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_4x4_SRGB_BLOCK :: Format

FORMAT_ASTC_4x4_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_5x4_UNORM_BLOCK :: Format

FORMAT_ASTC_5x4_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 5×4 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_5x4_SRGB_BLOCK :: Format

FORMAT_ASTC_5x4_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 5×4 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_5x5_UNORM_BLOCK :: Format

FORMAT_ASTC_5x5_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 5×5 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_5x5_SRGB_BLOCK :: Format

FORMAT_ASTC_5x5_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 5×5 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_6x5_UNORM_BLOCK :: Format

FORMAT_ASTC_6x5_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 6×5 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_6x5_SRGB_BLOCK :: Format

FORMAT_ASTC_6x5_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 6×5 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_6x6_UNORM_BLOCK :: Format

FORMAT_ASTC_6x6_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 6×6 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_6x6_SRGB_BLOCK :: Format

FORMAT_ASTC_6x6_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 6×6 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_8x5_UNORM_BLOCK :: Format

FORMAT_ASTC_8x5_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes an 8×5 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_8x5_SRGB_BLOCK :: Format

FORMAT_ASTC_8x5_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes an 8×5 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_8x6_UNORM_BLOCK :: Format

FORMAT_ASTC_8x6_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes an 8×6 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_8x6_SRGB_BLOCK :: Format

FORMAT_ASTC_8x6_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes an 8×6 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_8x8_UNORM_BLOCK :: Format

FORMAT_ASTC_8x8_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes an 8×8 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_8x8_SRGB_BLOCK :: Format

FORMAT_ASTC_8x8_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes an 8×8 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_10x5_UNORM_BLOCK :: Format

FORMAT_ASTC_10x5_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×5 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_10x5_SRGB_BLOCK :: Format

FORMAT_ASTC_10x5_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×5 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_10x6_UNORM_BLOCK :: Format

FORMAT_ASTC_10x6_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×6 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_10x6_SRGB_BLOCK :: Format

FORMAT_ASTC_10x6_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×6 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_10x8_UNORM_BLOCK :: Format

FORMAT_ASTC_10x8_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×8 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_10x8_SRGB_BLOCK :: Format

FORMAT_ASTC_10x8_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×8 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_10x10_UNORM_BLOCK :: Format

FORMAT_ASTC_10x10_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×10 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_10x10_SRGB_BLOCK :: Format

FORMAT_ASTC_10x10_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×10 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_12x10_UNORM_BLOCK :: Format

FORMAT_ASTC_12x10_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 12×10 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_12x10_SRGB_BLOCK :: Format

FORMAT_ASTC_12x10_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 12×10 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_ASTC_12x12_UNORM_BLOCK :: Format

FORMAT_ASTC_12x12_UNORM_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 12×12 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_ASTC_12x12_SRGB_BLOCK :: Format

FORMAT_ASTC_12x12_SRGB_BLOCK specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 12×12 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_A4B4G4R4_UNORM_PACK16_EXT :: Format

FORMAT_A4B4G4R4_UNORM_PACK16_EXT specifies a four-component, 16-bit packed unsigned normalized format that has a 4-bit A component in bits 12..15, a 4-bit B component in bits 8..11, a 4-bit G component in bits 4..7, and a 4-bit R component in bits 0..3.

pattern FORMAT_A4R4G4B4_UNORM_PACK16_EXT :: Format

FORMAT_A4R4G4B4_UNORM_PACK16_EXT specifies a four-component, 16-bit packed unsigned normalized format that has a 4-bit A component in bits 12..15, a 4-bit R component in bits 8..11, a 4-bit G component in bits 4..7, and a 4-bit B component in bits 0..3.

pattern FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 12×12 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 12×10 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×10 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×8 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×6 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 10×5 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 8×8 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 8×6 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 8×5 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 6×6 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 6×5 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 5×5 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 5×4 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT :: Format

FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT specifies a four-component, ASTC compressed format where each 128-bit compressed texel block encodes a 4×4 rectangle of signed floating-point RGBA texel data.

pattern FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG :: Format

FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG specifies a four-component, PVRTC compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG :: Format

FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG specifies a four-component, PVRTC compressed format where each 64-bit compressed texel block encodes an 8×4 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG :: Format

FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG specifies a four-component, PVRTC compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG :: Format

FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG specifies a four-component, PVRTC compressed format where each 64-bit compressed texel block encodes an 8×4 rectangle of unsigned normalized RGBA texel data with sRGB nonlinear encoding applied to the RGB components.

pattern FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG :: Format

FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG specifies a four-component, PVRTC compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG :: Format

FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG specifies a four-component, PVRTC compressed format where each 64-bit compressed texel block encodes an 8×4 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG :: Format

FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG specifies a four-component, PVRTC compressed format where each 64-bit compressed texel block encodes a 4×4 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG :: Format

FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG specifies a four-component, PVRTC compressed format where each 64-bit compressed texel block encodes an 8×4 rectangle of unsigned normalized RGBA texel data.

pattern FORMAT_G16_B16_R16_3PLANE_444_UNORM :: Format

FORMAT_G16_B16_R16_3PLANE_444_UNORM specifies an unsigned normalized multi-planar format that has a 16-bit G component in each 16-bit word of plane 0, a 16-bit B component in each 16-bit word of plane 1, and a 16-bit R component in each 16-bit word of plane 2. Each plane has the same dimensions and each R, G and B component contributes to a single texel. The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane.

pattern FORMAT_G16_B16R16_2PLANE_422_UNORM :: Format

FORMAT_G16_B16R16_2PLANE_422_UNORM specifies an unsigned normalized multi-planar format that has a 16-bit G component in each 16-bit word of plane 0, and a two-component, 32-bit BR plane 1 consisting of a 16-bit B component in the word in bytes 0..1, and a 16-bit R component in the word in bytes 2..3. The horizontal dimensions of the BR plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, and IMAGE_ASPECT_PLANE_1_BIT for the BR plane. Images in this format must be defined with a width that is a multiple of two.

pattern FORMAT_G16_B16_R16_3PLANE_422_UNORM :: Format

FORMAT_G16_B16_R16_3PLANE_422_UNORM specifies an unsigned normalized multi-planar format that has a 16-bit G component in each 16-bit word of plane 0, a 16-bit B component in each 16-bit word of plane 1, and a 16-bit R component in each 16-bit word of plane 2. The horizontal dimension of the R and B plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane. Images in this format must be defined with a width that is a multiple of two.

pattern FORMAT_G16_B16R16_2PLANE_420_UNORM :: Format

FORMAT_G16_B16R16_2PLANE_420_UNORM specifies an unsigned normalized multi-planar format that has a 16-bit G component in each 16-bit word of plane 0, and a two-component, 32-bit BR plane 1 consisting of a 16-bit B component in the word in bytes 0..1, and a 16-bit R component in the word in bytes 2..3. The horizontal and vertical dimensions of the BR plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R) and (leftlfloor j_G times 0.5 rightrfloor = j_B = j_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, and IMAGE_ASPECT_PLANE_1_BIT for the BR plane. Images in this format must be defined with a width and height that is a multiple of two.

pattern FORMAT_G16_B16_R16_3PLANE_420_UNORM :: Format

FORMAT_G16_B16_R16_3PLANE_420_UNORM specifies an unsigned normalized multi-planar format that has a 16-bit G component in each 16-bit word of plane 0, a 16-bit B component in each 16-bit word of plane 1, and a 16-bit R component in each 16-bit word of plane 2. The horizontal and vertical dimensions of the R and B planes are halved relative to the image dimensions, and each R and B component is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R) and (leftlfloor j_G times 0.5 rightrfloor = j_B = j_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane. Images in this format must be defined with a width and height that is a multiple of two.

pattern FORMAT_B16G16R16G16_422_UNORM :: Format

FORMAT_B16G16R16G16_422_UNORM specifies a four-component, 64-bit format containing a pair of G components, an R component, and a B component, collectively encoding a 2×1 rectangle of unsigned normalized RGB texel data. One G value is present at each i coordinate, with the B and R values shared across both G values and thus recorded at half the horizontal resolution of the image. This format has a 16-bit B component in the word in bytes 0..1, a 16-bit G component for the even i coordinate in the word in bytes 2..3, a 16-bit R component in the word in bytes 4..5, and a 16-bit G component for the odd i coordinate in the word in bytes 6..7. Images in this format must be defined with a width that is a multiple of two. For the purposes of the constraints on copy extents, this format is treated as a compressed format with a 2×1 compressed texel block.

pattern FORMAT_G16B16G16R16_422_UNORM :: Format

FORMAT_G16B16G16R16_422_UNORM specifies a four-component, 64-bit format containing a pair of G components, an R component, and a B component, collectively encoding a 2×1 rectangle of unsigned normalized RGB texel data. One G value is present at each i coordinate, with the B and R values shared across both G values and thus recorded at half the horizontal resolution of the image. This format has a 16-bit G component for the even i coordinate in the word in bytes 0..1, a 16-bit B component in the word in bytes 2..3, a 16-bit G component for the odd i coordinate in the word in bytes 4..5, and a 16-bit R component in the word in bytes 6..7. Images in this format must be defined with a width that is a multiple of two. For the purposes of the constraints on copy extents, this format is treated as a compressed format with a 2×1 compressed texel block.

pattern FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16 :: Format

FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 12-bit G component in the top 12 bits of each 16-bit word of plane 0, a 12-bit B component in the top 12 bits of each 16-bit word of plane 1, and a 12-bit R component in the top 12 bits of each 16-bit word of plane 2, with the bottom 4 bits of each word unused. Each plane has the same dimensions and each R, G and B component contributes to a single texel. The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane.

pattern FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16 :: Format

FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 12-bit G component in the top 12 bits of each 16-bit word of plane 0, and a two-component, 32-bit BR plane 1 consisting of a 12-bit B component in the top 12 bits of the word in bytes 0..1, and a 12-bit R component in the top 12 bits of the word in bytes 2..3, the bottom 4 bits of each word unused. The horizontal dimensions of the BR plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, and IMAGE_ASPECT_PLANE_1_BIT for the BR plane. Images in this format must be defined with a width that is a multiple of two.

pattern FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16 :: Format

FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 12-bit G component in the top 12 bits of each 16-bit word of plane 0, a 12-bit B component in the top 12 bits of each 16-bit word of plane 1, and a 12-bit R component in the top 12 bits of each 16-bit word of plane 2, with the bottom 4 bits of each word unused. The horizontal dimension of the R and B plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane. Images in this format must be defined with a width that is a multiple of two.

pattern FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16 :: Format

FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 12-bit G component in the top 12 bits of each 16-bit word of plane 0, and a two-component, 32-bit BR plane 1 consisting of a 12-bit B component in the top 12 bits of the word in bytes 0..1, and a 12-bit R component in the top 12 bits of the word in bytes 2..3, the bottom 4 bits of each word unused. The horizontal and vertical dimensions of the BR plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R) and (leftlfloor j_G times 0.5 rightrfloor = j_B = j_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, and IMAGE_ASPECT_PLANE_1_BIT for the BR plane. Images in this format must be defined with a width and height that is a multiple of two.

pattern FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16 :: Format

FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 12-bit G component in the top 12 bits of each 16-bit word of plane 0, a 12-bit B component in the top 12 bits of each 16-bit word of plane 1, and a 12-bit R component in the top 12 bits of each 16-bit word of plane 2, with the bottom 4 bits of each word unused. The horizontal and vertical dimensions of the R and B planes are halved relative to the image dimensions, and each R and B component is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R) and (leftlfloor j_G times 0.5 rightrfloor = j_B = j_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane. Images in this format must be defined with a width and height that is a multiple of two.

pattern FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16 :: Format

FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16 specifies a four-component, 64-bit format containing a pair of G components, an R component, and a B component, collectively encoding a 2×1 rectangle of unsigned normalized RGB texel data. One G value is present at each i coordinate, with the B and R values shared across both G values and thus recorded at half the horizontal resolution of the image. This format has a 12-bit B component in the top 12 bits of the word in bytes 0..1, a 12-bit G component for the even i coordinate in the top 12 bits of the word in bytes 2..3, a 12-bit R component in the top 12 bits of the word in bytes 4..5, and a 12-bit G component for the odd i coordinate in the top 12 bits of the word in bytes 6..7, with the bottom 4 bits of each word unused. Images in this format must be defined with a width that is a multiple of two. For the purposes of the constraints on copy extents, this format is treated as a compressed format with a 2×1 compressed texel block.

pattern FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16 :: Format

FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16 specifies a four-component, 64-bit format containing a pair of G components, an R component, and a B component, collectively encoding a 2×1 rectangle of unsigned normalized RGB texel data. One G value is present at each i coordinate, with the B and R values shared across both G values and thus recorded at half the horizontal resolution of the image. This format has a 12-bit G component for the even i coordinate in the top 12 bits of the word in bytes 0..1, a 12-bit B component in the top 12 bits of the word in bytes 2..3, a 12-bit G component for the odd i coordinate in the top 12 bits of the word in bytes 4..5, and a 12-bit R component in the top 12 bits of the word in bytes 6..7, with the bottom 4 bits of each word unused. Images in this format must be defined with a width that is a multiple of two. For the purposes of the constraints on copy extents, this format is treated as a compressed format with a 2×1 compressed texel block.

pattern FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16 :: Format

FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16 specifies a four-component, 64-bit unsigned normalized format that has a 12-bit R component in the top 12 bits of the word in bytes 0..1, a 12-bit G component in the top 12 bits of the word in bytes 2..3, a 12-bit B component in the top 12 bits of the word in bytes 4..5, and a 12-bit A component in the top 12 bits of the word in bytes 6..7, with the bottom 4 bits of each word unused.

pattern FORMAT_R12X4G12X4_UNORM_2PACK16 :: Format

FORMAT_R12X4G12X4_UNORM_2PACK16 specifies a two-component, 32-bit unsigned normalized format that has a 12-bit R component in the top 12 bits of the word in bytes 0..1, and a 12-bit G component in the top 12 bits of the word in bytes 2..3, with the bottom 4 bits of each word unused.

pattern FORMAT_R12X4_UNORM_PACK16 :: Format

FORMAT_R12X4_UNORM_PACK16 specifies a one-component, 16-bit unsigned normalized format that has a single 12-bit R component in the top 12 bits of a 16-bit word, with the bottom 4 bits unused.

pattern FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16 :: Format

FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 10-bit G component in the top 10 bits of each 16-bit word of plane 0, a 10-bit B component in the top 10 bits of each 16-bit word of plane 1, and a 10-bit R component in the top 10 bits of each 16-bit word of plane 2, with the bottom 6 bits of each word unused. Each plane has the same dimensions and each R, G and B component contributes to a single texel. The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane.

pattern FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16 :: Format

FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 10-bit G component in the top 10 bits of each 16-bit word of plane 0, and a two-component, 32-bit BR plane 1 consisting of a 10-bit B component in the top 10 bits of the word in bytes 0..1, and a 10-bit R component in the top 10 bits of the word in bytes 2..3, the bottom 6 bits of each word unused. The horizontal dimensions of the BR plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, and IMAGE_ASPECT_PLANE_1_BIT for the BR plane. Images in this format must be defined with a width that is a multiple of two.

pattern FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16 :: Format

FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 10-bit G component in the top 10 bits of each 16-bit word of plane 0, a 10-bit B component in the top 10 bits of each 16-bit word of plane 1, and a 10-bit R component in the top 10 bits of each 16-bit word of plane 2, with the bottom 6 bits of each word unused. The horizontal dimension of the R and B plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane. Images in this format must be defined with a width that is a multiple of two.

pattern FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16 :: Format

FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 10-bit G component in the top 10 bits of each 16-bit word of plane 0, and a two-component, 32-bit BR plane 1 consisting of a 10-bit B component in the top 10 bits of the word in bytes 0..1, and a 10-bit R component in the top 10 bits of the word in bytes 2..3, the bottom 6 bits of each word unused. The horizontal and vertical dimensions of the BR plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R) and (leftlfloor j_G times 0.5 rightrfloor = j_B = j_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, and IMAGE_ASPECT_PLANE_1_BIT for the BR plane. Images in this format must be defined with a width and height that is a multiple of two.

pattern FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16 :: Format

FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16 specifies an unsigned normalized multi-planar format that has a 10-bit G component in the top 10 bits of each 16-bit word of plane 0, a 10-bit B component in the top 10 bits of each 16-bit word of plane 1, and a 10-bit R component in the top 10 bits of each 16-bit word of plane 2, with the bottom 6 bits of each word unused. The horizontal and vertical dimensions of the R and B planes are halved relative to the image dimensions, and each R and B component is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R) and (leftlfloor j_G times 0.5 rightrfloor = j_B = j_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane. Images in this format must be defined with a width and height that is a multiple of two.

pattern FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16 :: Format

FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16 specifies a four-component, 64-bit format containing a pair of G components, an R component, and a B component, collectively encoding a 2×1 rectangle of unsigned normalized RGB texel data. One G value is present at each i coordinate, with the B and R values shared across both G values and thus recorded at half the horizontal resolution of the image. This format has a 10-bit B component in the top 10 bits of the word in bytes 0..1, a 10-bit G component for the even i coordinate in the top 10 bits of the word in bytes 2..3, a 10-bit R component in the top 10 bits of the word in bytes 4..5, and a 10-bit G component for the odd i coordinate in the top 10 bits of the word in bytes 6..7, with the bottom 6 bits of each word unused. Images in this format must be defined with a width that is a multiple of two. For the purposes of the constraints on copy extents, this format is treated as a compressed format with a 2×1 compressed texel block.

pattern FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16 :: Format

FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16 specifies a four-component, 64-bit format containing a pair of G components, an R component, and a B component, collectively encoding a 2×1 rectangle of unsigned normalized RGB texel data. One G value is present at each i coordinate, with the B and R values shared across both G values and thus recorded at half the horizontal resolution of the image. This format has a 10-bit G component for the even i coordinate in the top 10 bits of the word in bytes 0..1, a 10-bit B component in the top 10 bits of the word in bytes 2..3, a 10-bit G component for the odd i coordinate in the top 10 bits of the word in bytes 4..5, and a 10-bit R component in the top 10 bits of the word in bytes 6..7, with the bottom 6 bits of each word unused. Images in this format must be defined with a width that is a multiple of two. For the purposes of the constraints on copy extents, this format is treated as a compressed format with a 2×1 compressed texel block.

pattern FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16 :: Format

FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16 specifies a four-component, 64-bit unsigned normalized format that has a 10-bit R component in the top 10 bits of the word in bytes 0..1, a 10-bit G component in the top 10 bits of the word in bytes 2..3, a 10-bit B component in the top 10 bits of the word in bytes 4..5, and a 10-bit A component in the top 10 bits of the word in bytes 6..7, with the bottom 6 bits of each word unused.

pattern FORMAT_R10X6G10X6_UNORM_2PACK16 :: Format

FORMAT_R10X6G10X6_UNORM_2PACK16 specifies a two-component, 32-bit unsigned normalized format that has a 10-bit R component in the top 10 bits of the word in bytes 0..1, and a 10-bit G component in the top 10 bits of the word in bytes 2..3, with the bottom 6 bits of each word unused.

pattern FORMAT_R10X6_UNORM_PACK16 :: Format

FORMAT_R10X6_UNORM_PACK16 specifies a one-component, 16-bit unsigned normalized format that has a single 10-bit R component in the top 10 bits of a 16-bit word, with the bottom 6 bits unused.

pattern FORMAT_G8_B8_R8_3PLANE_444_UNORM :: Format

FORMAT_G8_B8_R8_3PLANE_444_UNORM specifies an unsigned normalized multi-planar format that has an 8-bit G component in plane 0, an 8-bit B component in plane 1, and an 8-bit R component in plane 2. Each plane has the same dimensions and each R, G and B component contributes to a single texel. The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane.

pattern FORMAT_G8_B8R8_2PLANE_422_UNORM :: Format

FORMAT_G8_B8R8_2PLANE_422_UNORM specifies an unsigned normalized multi-planar format that has an 8-bit G component in plane 0, and a two-component, 16-bit BR plane 1 consisting of an 8-bit B component in byte 0 and an 8-bit R component in byte 1. The horizontal dimensions of the BR plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, and IMAGE_ASPECT_PLANE_1_BIT for the BR plane. Images in this format must be defined with a width that is a multiple of two.

pattern FORMAT_G8_B8_R8_3PLANE_422_UNORM :: Format

FORMAT_G8_B8_R8_3PLANE_422_UNORM specifies an unsigned normalized multi-planar format that has an 8-bit G component in plane 0, an 8-bit B component in plane 1, and an 8-bit R component in plane 2. The horizontal dimension of the R and B plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane. Images in this format must be defined with a width that is a multiple of two.

pattern FORMAT_G8_B8R8_2PLANE_420_UNORM :: Format

FORMAT_G8_B8R8_2PLANE_420_UNORM specifies an unsigned normalized multi-planar format that has an 8-bit G component in plane 0, and a two-component, 16-bit BR plane 1 consisting of an 8-bit B component in byte 0 and an 8-bit R component in byte 1. The horizontal and vertical dimensions of the BR plane is halved relative to the image dimensions, and each R and B value is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R) and (leftlfloor j_G times 0.5 rightrfloor = j_B = j_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, and IMAGE_ASPECT_PLANE_1_BIT for the BR plane. Images in this format must be defined with a width and height that is a multiple of two.

pattern FORMAT_G8_B8_R8_3PLANE_420_UNORM :: Format

FORMAT_G8_B8_R8_3PLANE_420_UNORM specifies an unsigned normalized multi-planar format that has an 8-bit G component in plane 0, an 8-bit B component in plane 1, and an 8-bit R component in plane 2. The horizontal and vertical dimensions of the R and B planes are halved relative to the image dimensions, and each R and B component is shared with the G components for which (leftlfloor i_G times 0.5 rightrfloor = i_B = i_R) and (leftlfloor j_G times 0.5 rightrfloor = j_B = j_R). The location of each plane when this image is in linear layout can be determined via getImageSubresourceLayout, using IMAGE_ASPECT_PLANE_0_BIT for the G plane, IMAGE_ASPECT_PLANE_1_BIT for the B plane, and IMAGE_ASPECT_PLANE_2_BIT for the R plane. Images in this format must be defined with a width and height that is a multiple of two.

pattern FORMAT_B8G8R8G8_422_UNORM :: Format

FORMAT_B8G8R8G8_422_UNORM specifies a four-component, 32-bit format containing a pair of G components, an R component, and a B component, collectively encoding a 2×1 rectangle of unsigned normalized RGB texel data. One G value is present at each i coordinate, with the B and R values shared across both G values and thus recorded at half the horizontal resolution of the image. This format has an 8-bit B component in byte 0, an 8-bit G component for the even i coordinate in byte 1, an 8-bit R component in byte 2, and an 8-bit G component for the odd i coordinate in byte 3. Images in this format must be defined with a width that is a multiple of two. For the purposes of the constraints on copy extents, this format is treated as a compressed format with a 2×1 compressed texel block.

pattern FORMAT_G8B8G8R8_422_UNORM :: Format

FORMAT_G8B8G8R8_422_UNORM specifies a four-component, 32-bit format containing a pair of G components, an R component, and a B component, collectively encoding a 2×1 rectangle of unsigned normalized RGB texel data. One G value is present at each i coordinate, with the B and R values shared across both G values and thus recorded at half the horizontal resolution of the image. This format has an 8-bit G component for the even i coordinate in byte 0, an 8-bit B component in byte 1, an 8-bit G component for the odd i coordinate in byte 2, and an 8-bit R component in byte 3. Images in this format must be defined with a width that is a multiple of two. For the purposes of the constraints on copy extents, this format is treated as a compressed format with a 2×1 compressed texel block.

Instances

Instances details
Eq Format Source # 
Instance details

Defined in Vulkan.Core10.Enums.Format

Methods

(==) :: Format -> Format -> Bool #

(/=) :: Format -> Format -> Bool #

Ord Format Source # 
Instance details

Defined in Vulkan.Core10.Enums.Format

Read Format Source # 
Instance details

Defined in Vulkan.Core10.Enums.Format

Show Format Source # 
Instance details

Defined in Vulkan.Core10.Enums.Format

Storable Format Source # 
Instance details

Defined in Vulkan.Core10.Enums.Format

Zero Format Source # 
Instance details

Defined in Vulkan.Core10.Enums.Format

Methods

zero :: Format Source #

newtype StructureType Source #

VkStructureType - Vulkan structure types (sType)

Description

Each value corresponds to a particular structure with a sType member with a matching name. As a general rule, the name of each StructureType value is obtained by taking the name of the structure, stripping the leading Vk, prefixing each capital letter with _, converting the entire resulting string to upper case, and prefixing it with VK_STRUCTURE_TYPE_. For example, structures of type ImageCreateInfo correspond to a StructureType of STRUCTURE_TYPE_IMAGE_CREATE_INFO, and thus its sType member must equal that when it is passed to the API.

The values STRUCTURE_TYPE_LOADER_INSTANCE_CREATE_INFO and STRUCTURE_TYPE_LOADER_DEVICE_CREATE_INFO are reserved for internal use by the loader, and do not have corresponding Vulkan structures in this Specification.

See Also

AccelerationStructureBuildGeometryInfoKHR, AccelerationStructureCreateGeometryTypeInfoKHR, AccelerationStructureCreateInfoKHR, AccelerationStructureCreateInfoNV, AccelerationStructureDeviceAddressInfoKHR, AccelerationStructureGeometryAabbsDataKHR, AccelerationStructureGeometryInstancesDataKHR, AccelerationStructureGeometryKHR, AccelerationStructureGeometryTrianglesDataKHR, AccelerationStructureInfoNV, AccelerationStructureMemoryRequirementsInfoKHR, AccelerationStructureMemoryRequirementsInfoNV, AccelerationStructureVersionKHR, AcquireNextImageInfoKHR, AcquireProfilingLockInfoKHR, AndroidHardwareBufferFormatPropertiesANDROID, AndroidHardwareBufferPropertiesANDROID, AndroidHardwareBufferUsageANDROID, AndroidSurfaceCreateInfoKHR, ApplicationInfo, AttachmentDescription2, AttachmentDescriptionStencilLayout, AttachmentReference2, AttachmentReferenceStencilLayout, BaseInStructure, BaseOutStructure, BindAccelerationStructureMemoryInfoKHR, BindBufferMemoryDeviceGroupInfo, BindBufferMemoryInfo, BindImageMemoryDeviceGroupInfo, BindImageMemoryInfo, BindImageMemorySwapchainInfoKHR, BindImagePlaneMemoryInfo, BindSparseInfo, BufferCreateInfo, BufferDeviceAddressCreateInfoEXT, BufferDeviceAddressInfo, BufferMemoryBarrier, BufferMemoryRequirementsInfo2, BufferOpaqueCaptureAddressCreateInfo, BufferViewCreateInfo, CalibratedTimestampInfoEXT, CheckpointDataNV, CommandBufferAllocateInfo, CommandBufferBeginInfo, CommandBufferInheritanceConditionalRenderingInfoEXT, CommandBufferInheritanceInfo, CommandBufferInheritanceRenderPassTransformInfoQCOM, CommandPoolCreateInfo, ComputePipelineCreateInfo, ConditionalRenderingBeginInfoEXT, CooperativeMatrixPropertiesNV, CopyAccelerationStructureInfoKHR, CopyAccelerationStructureToMemoryInfoKHR, CopyDescriptorSet, CopyMemoryToAccelerationStructureInfoKHR, D3D12FenceSubmitInfoKHR, DebugMarkerMarkerInfoEXT, DebugMarkerObjectNameInfoEXT, DebugMarkerObjectTagInfoEXT, DebugReportCallbackCreateInfoEXT, DebugUtilsLabelEXT, DebugUtilsMessengerCallbackDataEXT, DebugUtilsMessengerCreateInfoEXT, DebugUtilsObjectNameInfoEXT, DebugUtilsObjectTagInfoEXT, DedicatedAllocationBufferCreateInfoNV, DedicatedAllocationImageCreateInfoNV, DedicatedAllocationMemoryAllocateInfoNV, DeferredOperationInfoKHR, DescriptorPoolCreateInfo, DescriptorPoolInlineUniformBlockCreateInfoEXT, DescriptorSetAllocateInfo, DescriptorSetLayoutBindingFlagsCreateInfo, DescriptorSetLayoutCreateInfo, DescriptorSetLayoutSupport, DescriptorSetVariableDescriptorCountAllocateInfo, DescriptorSetVariableDescriptorCountLayoutSupport, DescriptorUpdateTemplateCreateInfo, DeviceCreateInfo, DeviceDiagnosticsConfigCreateInfoNV, DeviceEventInfoEXT, DeviceGroupBindSparseInfo, DeviceGroupCommandBufferBeginInfo, DeviceGroupDeviceCreateInfo, DeviceGroupPresentCapabilitiesKHR, DeviceGroupPresentInfoKHR, DeviceGroupRenderPassBeginInfo, DeviceGroupSubmitInfo, DeviceGroupSwapchainCreateInfoKHR, DeviceMemoryOpaqueCaptureAddressInfo, DeviceMemoryOverallocationCreateInfoAMD, DevicePrivateDataCreateInfoEXT, DeviceQueueCreateInfo, DeviceQueueGlobalPriorityCreateInfoEXT, DeviceQueueInfo2, DirectFBSurfaceCreateInfoEXT, DisplayEventInfoEXT, DisplayModeCreateInfoKHR, DisplayModeProperties2KHR, DisplayNativeHdrSurfaceCapabilitiesAMD, DisplayPlaneCapabilities2KHR, DisplayPlaneInfo2KHR, DisplayPlaneProperties2KHR, DisplayPowerInfoEXT, DisplayPresentInfoKHR, DisplayProperties2KHR, DisplaySurfaceCreateInfoKHR, DrmFormatModifierPropertiesListEXT, EventCreateInfo, ExportFenceCreateInfo, ExportFenceWin32HandleInfoKHR, ExportMemoryAllocateInfo, ExportMemoryAllocateInfoNV, ExportMemoryWin32HandleInfoKHR, ExportMemoryWin32HandleInfoNV, ExportSemaphoreCreateInfo, ExportSemaphoreWin32HandleInfoKHR, ExternalBufferProperties, ExternalFenceProperties, ExternalFormatANDROID, ExternalImageFormatProperties, ExternalMemoryBufferCreateInfo, ExternalMemoryImageCreateInfo, ExternalMemoryImageCreateInfoNV, ExternalSemaphoreProperties, FenceCreateInfo, FenceGetFdInfoKHR, FenceGetWin32HandleInfoKHR, FilterCubicImageViewImageFormatPropertiesEXT, FormatProperties2, FramebufferAttachmentImageInfo, FramebufferAttachmentsCreateInfo, FramebufferCreateInfo, FramebufferMixedSamplesCombinationNV, GeneratedCommandsInfoNV, GeneratedCommandsMemoryRequirementsInfoNV, GeometryAABBNV, GeometryNV, GeometryTrianglesNV, GraphicsPipelineCreateInfo, GraphicsPipelineShaderGroupsCreateInfoNV, GraphicsShaderGroupCreateInfoNV, HdrMetadataEXT, HeadlessSurfaceCreateInfoEXT, IOSSurfaceCreateInfoMVK, ImageCreateInfo, ImageDrmFormatModifierExplicitCreateInfoEXT, ImageDrmFormatModifierListCreateInfoEXT, ImageDrmFormatModifierPropertiesEXT, ImageFormatListCreateInfo, ImageFormatProperties2, ImageMemoryBarrier, ImageMemoryRequirementsInfo2, ImagePipeSurfaceCreateInfoFUCHSIA, ImagePlaneMemoryRequirementsInfo, ImageSparseMemoryRequirementsInfo2, ImageStencilUsageCreateInfo, ImageSwapchainCreateInfoKHR, ImageViewASTCDecodeModeEXT, ImageViewAddressPropertiesNVX, ImageViewCreateInfo, ImageViewHandleInfoNVX, ImageViewUsageCreateInfo, ImportAndroidHardwareBufferInfoANDROID, ImportFenceFdInfoKHR, ImportFenceWin32HandleInfoKHR, ImportMemoryFdInfoKHR, ImportMemoryHostPointerInfoEXT, ImportMemoryWin32HandleInfoKHR, ImportMemoryWin32HandleInfoNV, ImportSemaphoreFdInfoKHR, ImportSemaphoreWin32HandleInfoKHR, IndirectCommandsLayoutCreateInfoNV, IndirectCommandsLayoutTokenNV, InitializePerformanceApiInfoINTEL, InstanceCreateInfo, MacOSSurfaceCreateInfoMVK, MappedMemoryRange, MemoryAllocateFlagsInfo, MemoryAllocateInfo, MemoryBarrier, MemoryDedicatedAllocateInfo, MemoryDedicatedRequirements, MemoryFdPropertiesKHR, MemoryGetAndroidHardwareBufferInfoANDROID, MemoryGetFdInfoKHR, MemoryGetWin32HandleInfoKHR, MemoryHostPointerPropertiesEXT, MemoryOpaqueCaptureAddressAllocateInfo, MemoryPriorityAllocateInfoEXT, MemoryRequirements2, MemoryWin32HandlePropertiesKHR, MetalSurfaceCreateInfoEXT, MultisamplePropertiesEXT, PerformanceConfigurationAcquireInfoINTEL, PerformanceCounterDescriptionKHR, PerformanceCounterKHR, PerformanceMarkerInfoINTEL, PerformanceOverrideInfoINTEL, PerformanceQuerySubmitInfoKHR, PerformanceStreamMarkerInfoINTEL, PhysicalDevice16BitStorageFeatures, PhysicalDevice4444FormatsFeaturesEXT, PhysicalDevice8BitStorageFeatures, PhysicalDeviceASTCDecodeFeaturesEXT, PhysicalDeviceBlendOperationAdvancedFeaturesEXT, PhysicalDeviceBlendOperationAdvancedPropertiesEXT, PhysicalDeviceBufferDeviceAddressFeatures, PhysicalDeviceBufferDeviceAddressFeaturesEXT, PhysicalDeviceCoherentMemoryFeaturesAMD, PhysicalDeviceComputeShaderDerivativesFeaturesNV, PhysicalDeviceConditionalRenderingFeaturesEXT, PhysicalDeviceConservativeRasterizationPropertiesEXT, PhysicalDeviceCooperativeMatrixFeaturesNV, PhysicalDeviceCooperativeMatrixPropertiesNV, PhysicalDeviceCornerSampledImageFeaturesNV, PhysicalDeviceCoverageReductionModeFeaturesNV, PhysicalDeviceCustomBorderColorFeaturesEXT, PhysicalDeviceCustomBorderColorPropertiesEXT, PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV, PhysicalDeviceDepthClipEnableFeaturesEXT, PhysicalDeviceDepthStencilResolveProperties, PhysicalDeviceDescriptorIndexingFeatures, PhysicalDeviceDescriptorIndexingProperties, PhysicalDeviceDeviceGeneratedCommandsFeaturesNV, PhysicalDeviceDeviceGeneratedCommandsPropertiesNV, PhysicalDeviceDiagnosticsConfigFeaturesNV, PhysicalDeviceDiscardRectanglePropertiesEXT, PhysicalDeviceDriverProperties, PhysicalDeviceExclusiveScissorFeaturesNV, PhysicalDeviceExtendedDynamicStateFeaturesEXT, PhysicalDeviceExternalBufferInfo, PhysicalDeviceExternalFenceInfo, PhysicalDeviceExternalImageFormatInfo, PhysicalDeviceExternalMemoryHostPropertiesEXT, PhysicalDeviceExternalSemaphoreInfo, PhysicalDeviceFeatures2, PhysicalDeviceFloatControlsProperties, PhysicalDeviceFragmentDensityMap2FeaturesEXT, PhysicalDeviceFragmentDensityMap2PropertiesEXT, PhysicalDeviceFragmentDensityMapFeaturesEXT, PhysicalDeviceFragmentDensityMapPropertiesEXT, PhysicalDeviceFragmentShaderBarycentricFeaturesNV, PhysicalDeviceFragmentShaderInterlockFeaturesEXT, PhysicalDeviceGroupProperties, PhysicalDeviceHostQueryResetFeatures, PhysicalDeviceIDProperties, PhysicalDeviceImageDrmFormatModifierInfoEXT, PhysicalDeviceImageFormatInfo2, PhysicalDeviceImageRobustnessFeaturesEXT, PhysicalDeviceImageViewImageFormatInfoEXT, PhysicalDeviceImagelessFramebufferFeatures, PhysicalDeviceIndexTypeUint8FeaturesEXT, PhysicalDeviceInlineUniformBlockFeaturesEXT, PhysicalDeviceInlineUniformBlockPropertiesEXT, PhysicalDeviceLineRasterizationFeaturesEXT, PhysicalDeviceLineRasterizationPropertiesEXT, PhysicalDeviceMaintenance3Properties, PhysicalDeviceMemoryBudgetPropertiesEXT, PhysicalDeviceMemoryPriorityFeaturesEXT, PhysicalDeviceMemoryProperties2, PhysicalDeviceMeshShaderFeaturesNV, PhysicalDeviceMeshShaderPropertiesNV, PhysicalDeviceMultiviewFeatures, PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX, PhysicalDeviceMultiviewProperties, PhysicalDevicePCIBusInfoPropertiesEXT, PhysicalDevicePerformanceQueryFeaturesKHR, PhysicalDevicePerformanceQueryPropertiesKHR, PhysicalDevicePipelineCreationCacheControlFeaturesEXT, PhysicalDevicePipelineExecutablePropertiesFeaturesKHR, PhysicalDevicePointClippingProperties, PhysicalDevicePrivateDataFeaturesEXT, PhysicalDeviceProperties2, PhysicalDeviceProtectedMemoryFeatures, PhysicalDeviceProtectedMemoryProperties, PhysicalDevicePushDescriptorPropertiesKHR, PhysicalDeviceRayTracingFeaturesKHR, PhysicalDeviceRayTracingPropertiesKHR, PhysicalDeviceRayTracingPropertiesNV, PhysicalDeviceRepresentativeFragmentTestFeaturesNV, PhysicalDeviceRobustness2FeaturesEXT, PhysicalDeviceRobustness2PropertiesEXT, PhysicalDeviceSampleLocationsPropertiesEXT, PhysicalDeviceSamplerFilterMinmaxProperties, PhysicalDeviceSamplerYcbcrConversionFeatures, PhysicalDeviceScalarBlockLayoutFeatures, PhysicalDeviceSeparateDepthStencilLayoutsFeatures, PhysicalDeviceShaderAtomicFloatFeaturesEXT, PhysicalDeviceShaderAtomicInt64Features, PhysicalDeviceShaderClockFeaturesKHR, PhysicalDeviceShaderCoreProperties2AMD, PhysicalDeviceShaderCorePropertiesAMD, PhysicalDeviceShaderDemoteToHelperInvocationFeaturesEXT, PhysicalDeviceShaderDrawParametersFeatures, PhysicalDeviceShaderFloat16Int8Features, PhysicalDeviceShaderImageFootprintFeaturesNV, PhysicalDeviceShaderIntegerFunctions2FeaturesINTEL, PhysicalDeviceShaderSMBuiltinsFeaturesNV, PhysicalDeviceShaderSMBuiltinsPropertiesNV, PhysicalDeviceShaderSubgroupExtendedTypesFeatures, PhysicalDeviceShadingRateImageFeaturesNV, PhysicalDeviceShadingRateImagePropertiesNV, PhysicalDeviceSparseImageFormatInfo2, PhysicalDeviceSubgroupProperties, PhysicalDeviceSubgroupSizeControlFeaturesEXT, PhysicalDeviceSubgroupSizeControlPropertiesEXT, PhysicalDeviceSurfaceInfo2KHR, PhysicalDeviceTexelBufferAlignmentFeaturesEXT, PhysicalDeviceTexelBufferAlignmentPropertiesEXT, PhysicalDeviceTextureCompressionASTCHDRFeaturesEXT, PhysicalDeviceTimelineSemaphoreFeatures, PhysicalDeviceTimelineSemaphoreProperties, PhysicalDeviceToolPropertiesEXT, PhysicalDeviceTransformFeedbackFeaturesEXT, PhysicalDeviceTransformFeedbackPropertiesEXT, PhysicalDeviceUniformBufferStandardLayoutFeatures, PhysicalDeviceVariablePointersFeatures, PhysicalDeviceVertexAttributeDivisorFeaturesEXT, PhysicalDeviceVertexAttributeDivisorPropertiesEXT, PhysicalDeviceVulkan11Features, PhysicalDeviceVulkan11Properties, PhysicalDeviceVulkan12Features, PhysicalDeviceVulkan12Properties, PhysicalDeviceVulkanMemoryModelFeatures, PhysicalDeviceYcbcrImageArraysFeaturesEXT, PipelineCacheCreateInfo, PipelineColorBlendAdvancedStateCreateInfoEXT, PipelineColorBlendStateCreateInfo, PipelineCompilerControlCreateInfoAMD, PipelineCoverageModulationStateCreateInfoNV, PipelineCoverageReductionStateCreateInfoNV, PipelineCoverageToColorStateCreateInfoNV, PipelineCreationFeedbackCreateInfoEXT, PipelineDepthStencilStateCreateInfo, PipelineDiscardRectangleStateCreateInfoEXT, PipelineDynamicStateCreateInfo, PipelineExecutableInfoKHR, PipelineExecutableInternalRepresentationKHR, PipelineExecutablePropertiesKHR, PipelineExecutableStatisticKHR, PipelineInfoKHR, PipelineInputAssemblyStateCreateInfo, PipelineLayoutCreateInfo, PipelineLibraryCreateInfoKHR, PipelineMultisampleStateCreateInfo, PipelineRasterizationConservativeStateCreateInfoEXT, PipelineRasterizationDepthClipStateCreateInfoEXT, PipelineRasterizationLineStateCreateInfoEXT, PipelineRasterizationStateCreateInfo, PipelineRasterizationStateRasterizationOrderAMD, PipelineRasterizationStateStreamCreateInfoEXT, PipelineRepresentativeFragmentTestStateCreateInfoNV, PipelineSampleLocationsStateCreateInfoEXT, PipelineShaderStageCreateInfo, PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT, PipelineTessellationDomainOriginStateCreateInfo, PipelineTessellationStateCreateInfo, PipelineVertexInputDivisorStateCreateInfoEXT, PipelineVertexInputStateCreateInfo, PipelineViewportCoarseSampleOrderStateCreateInfoNV, PipelineViewportExclusiveScissorStateCreateInfoNV, PipelineViewportShadingRateImageStateCreateInfoNV, PipelineViewportStateCreateInfo, PipelineViewportSwizzleStateCreateInfoNV, PipelineViewportWScalingStateCreateInfoNV, PresentFrameTokenGGP, PresentInfoKHR, PresentRegionsKHR, PresentTimesInfoGOOGLE, PrivateDataSlotCreateInfoEXT, ProtectedSubmitInfo, QueryPoolCreateInfo, QueryPoolPerformanceCreateInfoKHR, QueryPoolPerformanceQueryCreateInfoINTEL, QueueFamilyCheckpointPropertiesNV, QueueFamilyProperties2, RayTracingPipelineCreateInfoKHR, RayTracingPipelineCreateInfoNV, RayTracingPipelineInterfaceCreateInfoKHR, RayTracingShaderGroupCreateInfoKHR, RayTracingShaderGroupCreateInfoNV, RenderPassAttachmentBeginInfo, RenderPassBeginInfo, RenderPassCreateInfo, RenderPassCreateInfo2, RenderPassFragmentDensityMapCreateInfoEXT, RenderPassInputAttachmentAspectCreateInfo, RenderPassMultiviewCreateInfo, RenderPassSampleLocationsBeginInfoEXT, RenderPassTransformBeginInfoQCOM, SampleLocationsInfoEXT, SamplerCreateInfo, SamplerCustomBorderColorCreateInfoEXT, SamplerReductionModeCreateInfo, SamplerYcbcrConversionCreateInfo, SamplerYcbcrConversionImageFormatProperties, SamplerYcbcrConversionInfo, SemaphoreCreateInfo, SemaphoreGetFdInfoKHR, SemaphoreGetWin32HandleInfoKHR, SemaphoreSignalInfo, SemaphoreTypeCreateInfo, SemaphoreWaitInfo, ShaderModuleCreateInfo, ShaderModuleValidationCacheCreateInfoEXT, SharedPresentSurfaceCapabilitiesKHR, SparseImageFormatProperties2, SparseImageMemoryRequirements2, StreamDescriptorSurfaceCreateInfoGGP, SubmitInfo, SubpassBeginInfo, SubpassDependency2, SubpassDescription2, SubpassDescriptionDepthStencilResolve, SubpassEndInfo, SurfaceCapabilities2EXT, SurfaceCapabilities2KHR, SurfaceCapabilitiesFullScreenExclusiveEXT, SurfaceFormat2KHR, SurfaceFullScreenExclusiveInfoEXT, SurfaceFullScreenExclusiveWin32InfoEXT, SurfaceProtectedCapabilitiesKHR, SwapchainCounterCreateInfoEXT, SwapchainCreateInfoKHR, SwapchainDisplayNativeHdrCreateInfoAMD, TextureLODGatherFormatPropertiesAMD, TimelineSemaphoreSubmitInfo, ValidationCacheCreateInfoEXT, ValidationFeaturesEXT, ValidationFlagsEXT, ViSurfaceCreateInfoNN, WaylandSurfaceCreateInfoKHR, Win32KeyedMutexAcquireReleaseInfoKHR, Win32KeyedMutexAcquireReleaseInfoNV, Win32SurfaceCreateInfoKHR, WriteDescriptorSet, WriteDescriptorSetAccelerationStructureKHR, WriteDescriptorSetInlineUniformBlockEXT, XcbSurfaceCreateInfoKHR, XlibSurfaceCreateInfoKHR

Constructors

StructureType Int32 

Bundled Patterns

pattern STRUCTURE_TYPE_BUFFER_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_VIEW_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_INFO :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_POOL_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_COPY_DESCRIPTOR_SET :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_POOL_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_QUEUE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_APPLICATION_INFO :: StructureType 
pattern STRUCTURE_TYPE_INSTANCE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SUBMIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_MAPPED_MEMORY_RANGE :: StructureType 
pattern STRUCTURE_TYPE_BIND_SPARSE_INFO :: StructureType 
pattern STRUCTURE_TYPE_FENCE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EVENT_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SHADER_MODULE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_CACHE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_INPUT_ASSEMBLY_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_TESSELLATION_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_MULTISAMPLE_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_DEPTH_STENCIL_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_DYNAMIC_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_GRAPHICS_PIPELINE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMPUTE_PIPELINE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_LAYOUT_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_BARRIER :: StructureType 
pattern STRUCTURE_TYPE_LOADER_INSTANCE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_LOADER_DEVICE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DIRECTFB_SURFACE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_4444_FORMATS_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_ROBUSTNESS_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_2_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_DIAGNOSTICS_CONFIG_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DIAGNOSTICS_CONFIG_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_CREATION_CACHE_CONTROL_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PRIVATE_DATA_SLOT_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_PRIVATE_DATA_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIVATE_DATA_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_LIBRARY_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CUSTOM_BORDER_COLOR_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CUSTOM_BORDER_COLOR_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_CUSTOM_BORDER_COLOR_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_TRANSFORM_BEGIN_INFO_QCOM :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_RENDER_PASS_TRANSFORM_INFO_QCOM :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_GENERATED_COMMANDS_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_GENERATED_COMMANDS_MEMORY_REQUIREMENTS_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_GENERATED_COMMANDS_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_INDIRECT_COMMANDS_LAYOUT_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_INDIRECT_COMMANDS_LAYOUT_TOKEN_NV :: StructureType 
pattern STRUCTURE_TYPE_GRAPHICS_PIPELINE_SHADER_GROUPS_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_GRAPHICS_SHADER_GROUP_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_GENERATED_COMMANDS_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DEMOTE_TO_HELPER_INVOCATION_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INTERNAL_REPRESENTATION_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_EXECUTABLE_STATISTIC_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_EXECUTABLE_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_EXECUTABLE_PROPERTIES_FEATURES_KHR :: StructureType 
pattern STRUCTURE_TYPE_DEFERRED_OPERATION_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_INDEX_TYPE_UINT8_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_ATOMIC_FLOAT_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_LINE_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_HEADLESS_SURFACE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_WIN32_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_CAPABILITIES_FULL_SCREEN_EXCLUSIVE_EXT :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_YCBCR_IMAGE_ARRAYS_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_SHADER_INTERLOCK_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_FRAMEBUFFER_MIXED_SAMPLES_COMBINATION_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COVERAGE_REDUCTION_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COVERAGE_REDUCTION_MODE_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_VALIDATION_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TOOL_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_DEVICE_ADDRESS_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_BUFFER_DEVICE_ADDRESS_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEDICATED_ALLOCATION_IMAGE_ALIASING_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_PROTECTED_CAPABILITIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_PRIORITY_ALLOCATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PRIORITY_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_BUDGET_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COHERENT_MEMORY_FEATURES_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_2_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_SIZE_CONTROL_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_REQUIRED_SUBGROUP_SIZE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_SIZE_CONTROL_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_FRAGMENT_DENSITY_MAP_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_METAL_SURFACE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGEPIPE_SURFACE_CREATE_INFO_FUCHSIA :: StructureType 
pattern STRUCTURE_TYPE_SWAPCHAIN_DISPLAY_NATIVE_HDR_CREATE_INFO_AMD :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_NATIVE_HDR_SURFACE_CAPABILITIES_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PCI_BUS_INFO_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_INTEGER_FUNCTIONS_2_FEATURES_INTEL :: StructureType 
pattern STRUCTURE_TYPE_QUEUE_FAMILY_CHECKPOINT_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_CHECKPOINT_DATA_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXCLUSIVE_SCISSOR_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_EXCLUSIVE_SCISSOR_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_IMAGE_FOOTPRINT_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_SHADER_BARYCENTRIC_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COMPUTE_SHADER_DERIVATIVES_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_CREATION_FEEDBACK_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PRESENT_FRAME_TOKEN_GGP :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_DIVISOR_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_MEMORY_OVERALLOCATION_CREATE_INFO_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_AMD :: StructureType 
pattern STRUCTURE_TYPE_CALIBRATED_TIMESTAMP_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COMPILER_CONTROL_CREATE_INFO_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CLOCK_FEATURES_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_HOST_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_HOST_POINTER_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_MEMORY_HOST_POINTER_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_QUEUE_GLOBAL_PRIORITY_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_FILTER_CUBIC_IMAGE_VIEW_IMAGE_FORMAT_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_VIEW_IMAGE_FORMAT_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_REPRESENTATIVE_FRAGMENT_TEST_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_REPRESENTATIVE_FRAGMENT_TEST_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_SHADER_GROUP_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_GEOMETRY_AABB_NV :: StructureType 
pattern STRUCTURE_TYPE_GEOMETRY_TRIANGLES_NV :: StructureType 
pattern STRUCTURE_TYPE_GEOMETRY_NV :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_PIPELINE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_COARSE_SAMPLE_ORDER_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADING_RATE_IMAGE_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADING_RATE_IMAGE_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_SHADING_RATE_IMAGE_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_SHADER_MODULE_VALIDATION_CACHE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_VALIDATION_CACHE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_EXPLICIT_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_LIST_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_DRM_FORMAT_MODIFIER_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_LIST_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COVERAGE_MODULATION_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_PIPELINE_INTERFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_SHADER_GROUP_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_PIPELINE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_FEATURES_KHR :: StructureType 
pattern STRUCTURE_TYPE_COPY_MEMORY_TO_ACCELERATION_STRUCTURE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_TO_MEMORY_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_VERSION_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_TRIANGLES_DATA_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_INSTANCES_DATA_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_AABBS_DATA_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_DEVICE_ADDRESS_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_GEOMETRY_TYPE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_BUILD_GEOMETRY_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET_ACCELERATION_STRUCTURE_KHR :: StructureType 
pattern STRUCTURE_TYPE_BIND_ACCELERATION_STRUCTURE_MEMORY_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COVERAGE_TO_COLOR_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_ADVANCED_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_MULTISAMPLE_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SAMPLE_LOCATIONS_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_SAMPLE_LOCATIONS_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_SAMPLE_LOCATIONS_BEGIN_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_SAMPLE_LOCATIONS_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_POOL_INLINE_UNIFORM_BLOCK_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET_INLINE_UNIFORM_BLOCK_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_INLINE_UNIFORM_BLOCK_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_INLINE_UNIFORM_BLOCK_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_FORMAT_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_GET_ANDROID_HARDWARE_BUFFER_INFO_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_ANDROID_HARDWARE_BUFFER_INFO_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_USAGE_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_MESSENGER_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_MESSENGER_CALLBACK_DATA_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_LABEL_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_OBJECT_TAG_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_OBJECT_NAME_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_MACOS_SURFACE_CREATE_INFO_MVK :: StructureType 
pattern STRUCTURE_TYPE_IOS_SURFACE_CREATE_INFO_MVK :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PLANE_CAPABILITIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PLANE_INFO_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_MODE_PROPERTIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PLANE_PROPERTIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PROPERTIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_FORMAT_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_CAPABILITIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SURFACE_INFO_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_COUNTER_DESCRIPTION_KHR :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_COUNTER_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACQUIRE_PROFILING_LOCK_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_QUERY_SUBMIT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PERFORMANCE_QUERY_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PERFORMANCE_QUERY_FEATURES_KHR :: StructureType 
pattern STRUCTURE_TYPE_FENCE_GET_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_FENCE_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_FENCE_GET_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_FENCE_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_FENCE_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_SHARED_PRESENT_SURFACE_CAPABILITIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_HDR_METADATA_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_DEPTH_CLIP_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLIP_ENABLE_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_CONSERVATIVE_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CONSERVATIVE_RASTERIZATION_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_DISCARD_RECTANGLE_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DISCARD_RECTANGLE_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_SWIZZLE_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PER_VIEW_ATTRIBUTES_PROPERTIES_NVX :: StructureType 
pattern STRUCTURE_TYPE_PRESENT_TIMES_INFO_GOOGLE :: StructureType 
pattern STRUCTURE_TYPE_SWAPCHAIN_COUNTER_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_EVENT_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_EVENT_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_POWER_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_CAPABILITIES_2_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_W_SCALING_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PRESENT_REGIONS_KHR :: StructureType 
pattern STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PUSH_DESCRIPTOR_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_GET_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_SEMAPHORE_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_GET_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_D3D12_FENCE_SUBMIT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_SEMAPHORE_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_SEMAPHORE_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_GET_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_FD_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_MEMORY_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_GET_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_WIN32_HANDLE_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_ASTC_DECODE_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_ASTC_DECODE_MODE_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXTURE_COMPRESSION_ASTC_HDR_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_VI_SURFACE_CREATE_INFO_NN :: StructureType 
pattern STRUCTURE_TYPE_VALIDATION_FLAGS_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_SWAPCHAIN_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACQUIRE_NEXT_IMAGE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_BIND_IMAGE_MEMORY_SWAPCHAIN_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_SWAPCHAIN_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_CAPABILITIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CORNER_SAMPLED_IMAGE_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_STREAM_DESCRIPTOR_SURFACE_CREATE_INFO_GGP :: StructureType 
pattern STRUCTURE_TYPE_TEXTURE_LOD_GATHER_FORMAT_PROPERTIES_AMD :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_ADDRESS_PROPERTIES_NVX :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_HANDLE_INFO_NVX :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_STREAM_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TRANSFORM_FEEDBACK_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TRANSFORM_FEEDBACK_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEDICATED_ALLOCATION_MEMORY_ALLOCATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_DEDICATED_ALLOCATION_BUFFER_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_DEDICATED_ALLOCATION_IMAGE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_MARKER_MARKER_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_TAG_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_NAME_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_RASTERIZATION_ORDER_AMD :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_WIN32_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ANDROID_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_WAYLAND_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_XCB_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_XLIB_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PRESENT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_MODE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PRESENT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_SWAPCHAIN_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_MEMORY_OPAQUE_CAPTURE_ADDRESS_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_OPAQUE_CAPTURE_ADDRESS_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_OPAQUE_CAPTURE_ADDRESS_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_DEVICE_ADDRESS_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_BUFFER_DEVICE_ADDRESS_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_SIGNAL_INFO :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_WAIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_TIMELINE_SEMAPHORE_SUBMIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_TYPE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TIMELINE_SEMAPHORE_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TIMELINE_SEMAPHORE_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_HOST_QUERY_RESET_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_STENCIL_LAYOUT :: StructureType 
pattern STRUCTURE_TYPE_ATTACHMENT_REFERENCE_STENCIL_LAYOUT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SEPARATE_DEPTH_STENCIL_LAYOUTS_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SUBGROUP_EXTENDED_TYPES_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_UNIFORM_BUFFER_STANDARD_LAYOUT_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_ATTACHMENT_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENT_IMAGE_INFO :: StructureType 
pattern STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENTS_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGELESS_FRAMEBUFFER_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_MEMORY_MODEL_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_REDUCTION_MODE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SAMPLER_FILTER_MINMAX_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_STENCIL_USAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SCALAR_BLOCK_LAYOUT_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_DESCRIPTION_DEPTH_STENCIL_RESOLVE :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_STENCIL_RESOLVE_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_LAYOUT_SUPPORT :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_BINDING_FLAGS_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FLOAT_CONTROLS_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_FLOAT16_INT8_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_ATOMIC_INT64_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DRIVER_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_8BIT_STORAGE_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_END_INFO :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_DEPENDENCY_2 :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2 :: StructureType 
pattern STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2 :: StructureType 
pattern STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_2 :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_FORMAT_LIST_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DRAW_PARAMETERS_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_SUPPORT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MAINTENANCE_3_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_SEMAPHORE_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_SEMAPHORE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_SEMAPHORE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_FENCE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_FENCE_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FENCE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_MEMORY_BUFFER_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_ID_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_BUFFER_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_BUFFER_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_IMAGE_FORMAT_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_IMAGE_FORMAT_INFO :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_YCBCR_CONVERSION_IMAGE_FORMAT_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SAMPLER_YCBCR_CONVERSION_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_PLANE_MEMORY_REQUIREMENTS_INFO :: StructureType 
pattern STRUCTURE_TYPE_BIND_IMAGE_PLANE_MEMORY_INFO :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_YCBCR_CONVERSION_INFO :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_YCBCR_CONVERSION_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_QUEUE_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PROTECTED_MEMORY_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PROTECTED_MEMORY_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PROTECTED_SUBMIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VARIABLE_POINTERS_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_MULTIVIEW_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_TESSELLATION_DOMAIN_ORIGIN_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_USAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_INPUT_ATTACHMENT_ASPECT_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_POINT_CLIPPING_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SPARSE_IMAGE_FORMAT_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_SPARSE_IMAGE_FORMAT_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_QUEUE_FAMILY_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_FORMAT_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_FORMAT_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_FORMAT_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FEATURES_2 :: StructureType 
pattern STRUCTURE_TYPE_SPARSE_IMAGE_MEMORY_REQUIREMENTS_2 :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_REQUIREMENTS_2 :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_SPARSE_MEMORY_REQUIREMENTS_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_MEMORY_REQUIREMENTS_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_MEMORY_REQUIREMENTS_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_DEVICE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_GROUP_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_BIND_IMAGE_MEMORY_DEVICE_GROUP_INFO :: StructureType 
pattern STRUCTURE_TYPE_BIND_BUFFER_MEMORY_DEVICE_GROUP_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_DEDICATED_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_DEDICATED_REQUIREMENTS :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_16BIT_STORAGE_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_BIND_IMAGE_MEMORY_INFO :: StructureType 
pattern STRUCTURE_TYPE_BIND_BUFFER_MEMORY_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_PROPERTIES :: StructureType 

Instances

Instances details
Eq StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Ord StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Read StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Show StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Storable StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Zero StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

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

ObjectType 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 ImageCreateFlagBits Source #

VkImageCreateFlagBits - Bitmask specifying additional parameters of an image

Description

See Sparse Resource Features and Sparse Physical Device Features for more details.

See Also

ImageCreateFlags

Bundled Patterns

pattern IMAGE_CREATE_SPARSE_BINDING_BIT :: ImageCreateFlagBits

IMAGE_CREATE_SPARSE_BINDING_BIT specifies that the image will be backed using sparse memory binding.

pattern IMAGE_CREATE_SPARSE_RESIDENCY_BIT :: ImageCreateFlagBits

IMAGE_CREATE_SPARSE_RESIDENCY_BIT specifies that the image can be partially backed using sparse memory binding. Images created with this flag must also be created with the IMAGE_CREATE_SPARSE_BINDING_BIT flag.

pattern IMAGE_CREATE_SPARSE_ALIASED_BIT :: ImageCreateFlagBits

IMAGE_CREATE_SPARSE_ALIASED_BIT specifies that the image will be backed using sparse memory binding with memory ranges that might also simultaneously be backing another image (or another portion of the same image). Images created with this flag must also be created with the IMAGE_CREATE_SPARSE_BINDING_BIT flag

pattern IMAGE_CREATE_MUTABLE_FORMAT_BIT :: ImageCreateFlagBits

IMAGE_CREATE_MUTABLE_FORMAT_BIT specifies that the image can be used to create a ImageView with a different format from the image. For multi-planar formats, IMAGE_CREATE_MUTABLE_FORMAT_BIT specifies that a ImageView can be created of a plane of the image.

pattern IMAGE_CREATE_CUBE_COMPATIBLE_BIT :: ImageCreateFlagBits

IMAGE_CREATE_CUBE_COMPATIBLE_BIT specifies that the image can be used to create a ImageView of type IMAGE_VIEW_TYPE_CUBE or IMAGE_VIEW_TYPE_CUBE_ARRAY.

pattern IMAGE_CREATE_SUBSAMPLED_BIT_EXT :: ImageCreateFlagBits

IMAGE_CREATE_SUBSAMPLED_BIT_EXT specifies that an image can be in a subsampled format which may be more optimal when written as an attachment by a render pass that has a fragment density map attachment. Accessing a subsampled image has additional considerations:

pattern IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT :: ImageCreateFlagBits

IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT specifies that an image with a depth or depth/stencil format can be used with custom sample locations when used as a depth/stencil attachment.

pattern IMAGE_CREATE_CORNER_SAMPLED_BIT_NV :: ImageCreateFlagBits

IMAGE_CREATE_CORNER_SAMPLED_BIT_NV specifies that the image is a corner-sampled image.

pattern IMAGE_CREATE_DISJOINT_BIT :: ImageCreateFlagBits

IMAGE_CREATE_DISJOINT_BIT specifies that an image with a multi-planar format must have each plane separately bound to memory, rather than having a single memory binding for the whole image; the presence of this bit distinguishes a disjoint image from an image without this bit set.

pattern IMAGE_CREATE_PROTECTED_BIT :: ImageCreateFlagBits

IMAGE_CREATE_PROTECTED_BIT specifies that the image is a protected image.

pattern IMAGE_CREATE_EXTENDED_USAGE_BIT :: ImageCreateFlagBits

IMAGE_CREATE_EXTENDED_USAGE_BIT specifies that the image can be created with usage flags that are not supported for the format the image is created with but are supported for at least one format a ImageView created from the image can have.

pattern IMAGE_CREATE_BLOCK_TEXEL_VIEW_COMPATIBLE_BIT :: ImageCreateFlagBits

IMAGE_CREATE_BLOCK_TEXEL_VIEW_COMPATIBLE_BIT specifies that the image having a compressed format can be used to create a ImageView with an uncompressed format where each texel in the image view corresponds to a compressed texel block of the image.

pattern IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT :: ImageCreateFlagBits

IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT specifies that the image can be used to create a ImageView of type IMAGE_VIEW_TYPE_2D or IMAGE_VIEW_TYPE_2D_ARRAY.

pattern IMAGE_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT :: ImageCreateFlagBits

IMAGE_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT specifies that the image can be used with a non-zero value of the splitInstanceBindRegionCount member of a BindImageMemoryDeviceGroupInfo structure passed into bindImageMemory2. This flag also has the effect of making the image use the standard sparse image block dimensions.

pattern IMAGE_CREATE_ALIAS_BIT :: ImageCreateFlagBits

IMAGE_CREATE_ALIAS_BIT specifies that two images created with the same creation parameters and aliased to the same memory can interpret the contents of the memory consistently with each other, subject to the rules described in the Memory Aliasing section. This flag further specifies that each plane of a disjoint image can share an in-memory non-linear representation with single-plane images, and that a single-plane image can share an in-memory non-linear representation with a plane of a multi-planar disjoint image, according to the rules in https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-compatible-planes. If the pNext chain includes a ExternalMemoryImageCreateInfo or ExternalMemoryImageCreateInfoNV structure whose handleTypes member is not 0, it is as if IMAGE_CREATE_ALIAS_BIT is set.

Instances

Instances details
Eq ImageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageCreateFlagBits

Ord ImageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageCreateFlagBits

Read ImageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageCreateFlagBits

Show ImageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageCreateFlagBits

Storable ImageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageCreateFlagBits

Bits ImageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageCreateFlagBits

Zero ImageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageCreateFlagBits

newtype FormatFeatureFlagBits Source #

VkFormatFeatureFlagBits - Bitmask specifying features supported by a buffer

Description

The following bits may be set in linearTilingFeatures, optimalTilingFeatures, and DrmFormatModifierPropertiesEXT::drmFormatModifierTilingFeatures, specifying that the features are supported by images or image views or sampler Y′CBCR conversion objects created with the queried getPhysicalDeviceFormatProperties::format:

The following bits may be set in bufferFeatures, specifying that the features are supported by buffers or buffer views created with the queried getPhysicalDeviceProperties::format:

See Also

FormatFeatureFlags

Bundled Patterns

pattern FORMAT_FEATURE_SAMPLED_IMAGE_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_SAMPLED_IMAGE_BIT specifies that an image view can be sampled from.

pattern FORMAT_FEATURE_STORAGE_IMAGE_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_STORAGE_IMAGE_BIT specifies that an image view can be used as a storage images.

pattern FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT specifies that an image view can be used as storage image that supports atomic operations.

pattern FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT specifies that the format can be used to create a buffer view that can be bound to a DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER descriptor.

pattern FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT specifies that the format can be used to create a buffer view that can be bound to a DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER descriptor.

pattern FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT specifies that atomic operations are supported on DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER with this format.

pattern FORMAT_FEATURE_VERTEX_BUFFER_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_VERTEX_BUFFER_BIT specifies that the format can be used as a vertex attribute format (VertexInputAttributeDescription::format).

pattern FORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_COLOR_ATTACHMENT_BIT specifies that an image view can be used as a framebuffer color attachment and as an input attachment.

pattern FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT specifies that an image view can be used as a framebuffer color attachment that supports blending and as an input attachment.

pattern FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT specifies that an image view can be used as a framebuffer depth/stencil attachment and as an input attachment.

pattern FORMAT_FEATURE_BLIT_SRC_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_BLIT_SRC_BIT specifies that an image can be used as srcImage for the cmdBlitImage command.

pattern FORMAT_FEATURE_BLIT_DST_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_BLIT_DST_BIT specifies that an image can be used as dstImage for the cmdBlitImage command.

pattern FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT specifies that if FORMAT_FEATURE_SAMPLED_IMAGE_BIT is also set, an image view can be used with a sampler that has either of magFilter or minFilter set to FILTER_LINEAR, or mipmapMode set to SAMPLER_MIPMAP_MODE_LINEAR. If FORMAT_FEATURE_BLIT_SRC_BIT is also set, an image can be used as the srcImage to cmdBlitImage with a filter of FILTER_LINEAR. This bit must only be exposed for formats that also support the FORMAT_FEATURE_SAMPLED_IMAGE_BIT or FORMAT_FEATURE_BLIT_SRC_BIT.

If the format being queried is a depth/stencil format, this bit only specifies that the depth aspect (not the stencil aspect) of an image of this format supports linear filtering, and that linear filtering of the depth aspect is supported whether depth compare is enabled in the sampler or not. If this bit is not present, linear filtering with depth compare disabled is unsupported and linear filtering with depth compare enabled is supported, but may compute the filtered value in an implementation-dependent manner which differs from the normal rules of linear filtering. The resulting value must be in the range [0,1] and should be proportional to, or a weighted average of, the number of comparison passes or failures.

pattern FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT :: FormatFeatureFlagBits

FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT specifies that an image view can be used as a fragment density map attachment.

pattern FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR :: FormatFeatureFlagBits 
pattern FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_IMG :: FormatFeatureFlagBits 
pattern FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT specifies Image can be used as a sampled image with a min or max SamplerReductionMode. This bit must only be exposed for formats that also support the FORMAT_FEATURE_SAMPLED_IMAGE_BIT.

pattern FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT specifies that an application can define a sampler Y′CBCR conversion using this format as a source, and that an image of this format can be used with a SamplerYcbcrConversionCreateInfo xChromaOffset and/or yChromaOffset of CHROMA_LOCATION_COSITED_EVEN. Otherwise both xChromaOffset and yChromaOffset must be CHROMA_LOCATION_MIDPOINT. If neither FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT nor FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT is set, the application must not define a sampler Y′CBCR conversion using this format as a source.

pattern FORMAT_FEATURE_DISJOINT_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_DISJOINT_BIT specifies that a multi-planar image can have the IMAGE_CREATE_DISJOINT_BIT set during image creation. An implementation must not set FORMAT_FEATURE_DISJOINT_BIT for single-plane formats.

pattern FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT specifies that reconstruction can be forcibly made explicit by setting SamplerYcbcrConversionCreateInfo::forceExplicitReconstruction to TRUE. If the format being queried supports FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT it must also support FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT.

pattern FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT specifies that reconstruction is explicit, as described in https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-chroma-reconstruction. If this bit is not present, reconstruction is implicit by default.

pattern FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT specifies that the format can have different chroma, min, and mag filters.

pattern FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT specifies that the format can do linear sampler filtering (min/magFilter) whilst sampler Y′CBCR conversion is enabled.

pattern FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT specifies that an application can define a sampler Y′CBCR conversion using this format as a source, and that an image of this format can be used with a SamplerYcbcrConversionCreateInfo xChromaOffset and/or yChromaOffset of CHROMA_LOCATION_MIDPOINT. Otherwise both xChromaOffset and yChromaOffset must be CHROMA_LOCATION_COSITED_EVEN. If a format does not incorporate chroma downsampling (it is not a “422” or “420” format) but the implementation supports sampler Y′CBCR conversion for this format, the implementation must set FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT.

pattern FORMAT_FEATURE_TRANSFER_DST_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_TRANSFER_DST_BIT specifies that an image can be used as a destination image for copy commands and clear commands.

pattern FORMAT_FEATURE_TRANSFER_SRC_BIT :: FormatFeatureFlagBits

FORMAT_FEATURE_TRANSFER_SRC_BIT specifies that an image can be used as a source image for copy commands.

Instances

Instances details
Eq FormatFeatureFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.FormatFeatureFlagBits

Ord FormatFeatureFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.FormatFeatureFlagBits

Read FormatFeatureFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.FormatFeatureFlagBits

Show FormatFeatureFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.FormatFeatureFlagBits

Storable FormatFeatureFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.FormatFeatureFlagBits

Bits FormatFeatureFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.FormatFeatureFlagBits

Zero FormatFeatureFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.FormatFeatureFlagBits

newtype ImageAspectFlagBits Source #

VkImageAspectFlagBits - Bitmask specifying which aspects of an image are included in a view

See Also

BindImagePlaneMemoryInfo, ImageAspectFlags, ImagePlaneMemoryRequirementsInfo

Instances

Instances details
Eq ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Ord ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Read ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Show ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Storable ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Bits ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

Zero ImageAspectFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageAspectFlagBits

newtype SamplerYcbcrModelConversion Source #

VkSamplerYcbcrModelConversion - Color model component of a color space

Description

In the VK_SAMPLER_YCBCR_MODEL_CONVERSION_YCBCR_* color models, for the input to the sampler Y′CBCR range expansion and model conversion:

  • the Y (Y′ luma) channel corresponds to the G channel of an RGB image.
  • the CB (CB or “U” blue color difference) channel corresponds to the B channel of an RGB image.
  • the CR (CR or “V” red color difference) channel corresponds to the R channel of an RGB image.
  • the alpha channel, if present, is not modified by color model conversion.

These rules reflect the mapping of channels after the channel swizzle operation (controlled by SamplerYcbcrConversionCreateInfo::components).

Note

For example, an “YUVA” 32-bit format comprising four 8-bit channels can be implemented as FORMAT_R8G8B8A8_UNORM with a component mapping:

See Also

AndroidHardwareBufferFormatPropertiesANDROID, SamplerYcbcrConversionCreateInfo

Instances

Instances details
Eq SamplerYcbcrModelConversion Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrModelConversion

Ord SamplerYcbcrModelConversion Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrModelConversion

Read SamplerYcbcrModelConversion Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrModelConversion

Show SamplerYcbcrModelConversion Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrModelConversion

Storable SamplerYcbcrModelConversion Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrModelConversion

Zero SamplerYcbcrModelConversion Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrModelConversion

newtype SamplerYcbcrRange Source #

VkSamplerYcbcrRange - Range of encoded values in a color space

Description

The formulae for these conversions is described in the Sampler Y′CBCR Range Expansion section of the Image Operations chapter.

No range modification takes place if ycbcrModel is SAMPLER_YCBCR_MODEL_CONVERSION_RGB_IDENTITY; the ycbcrRange field of SamplerYcbcrConversionCreateInfo is ignored in this case.

See Also

AndroidHardwareBufferFormatPropertiesANDROID, SamplerYcbcrConversionCreateInfo

Constructors

SamplerYcbcrRange Int32 

Bundled Patterns

pattern SAMPLER_YCBCR_RANGE_ITU_FULL :: SamplerYcbcrRange

SAMPLER_YCBCR_RANGE_ITU_FULL specifies that the full range of the encoded values are valid and interpreted according to the ITU “full range” quantization rules.

pattern SAMPLER_YCBCR_RANGE_ITU_NARROW :: SamplerYcbcrRange

SAMPLER_YCBCR_RANGE_ITU_NARROW specifies that headroom and foot room are reserved in the numerical range of encoded values, and the remaining values are expanded according to the ITU “narrow range” quantization rules.

Instances

Instances details
Eq SamplerYcbcrRange Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrRange

Ord SamplerYcbcrRange Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrRange

Read SamplerYcbcrRange Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrRange

Show SamplerYcbcrRange Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrRange

Storable SamplerYcbcrRange Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrRange

Zero SamplerYcbcrRange Source # 
Instance details

Defined in Vulkan.Core11.Enums.SamplerYcbcrRange

newtype ChromaLocation Source #

VkChromaLocation - Position of downsampled chroma samples

See Also

AndroidHardwareBufferFormatPropertiesANDROID, SamplerYcbcrConversionCreateInfo

Constructors

ChromaLocation Int32 

Bundled Patterns

pattern CHROMA_LOCATION_COSITED_EVEN :: ChromaLocation

CHROMA_LOCATION_COSITED_EVEN specifies that downsampled chroma samples are aligned with luma samples with even coordinates.

pattern CHROMA_LOCATION_MIDPOINT :: ChromaLocation

CHROMA_LOCATION_MIDPOINT specifies that downsampled chroma samples are located half way between each even luma sample and the nearest higher odd luma sample.

Instances

Instances details
Eq ChromaLocation Source # 
Instance details

Defined in Vulkan.Core11.Enums.ChromaLocation

Ord ChromaLocation Source # 
Instance details

Defined in Vulkan.Core11.Enums.ChromaLocation

Read ChromaLocation Source # 
Instance details

Defined in Vulkan.Core11.Enums.ChromaLocation

Show ChromaLocation Source # 
Instance details

Defined in Vulkan.Core11.Enums.ChromaLocation

Storable ChromaLocation Source # 
Instance details

Defined in Vulkan.Core11.Enums.ChromaLocation

Zero ChromaLocation Source # 
Instance details

Defined in Vulkan.Core11.Enums.ChromaLocation