| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Vulkan.Core10.DeviceInitialization
Synopsis
- createInstance :: forall a io. (Extendss InstanceCreateInfo a, PokeChain a, MonadIO io) => InstanceCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io Instance
- withInstance :: forall a io r. (Extendss InstanceCreateInfo a, PokeChain a, MonadIO io) => InstanceCreateInfo a -> Maybe AllocationCallbacks -> (io Instance -> (Instance -> io ()) -> r) -> r
- destroyInstance :: forall io. MonadIO io => Instance -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
- enumeratePhysicalDevices :: forall io. MonadIO io => Instance -> io (Result, "physicalDevices" ::: Vector PhysicalDevice)
- getDeviceProcAddr :: forall io. MonadIO io => Device -> ("name" ::: ByteString) -> io PFN_vkVoidFunction
- getInstanceProcAddr :: forall io. MonadIO io => Instance -> ("name" ::: ByteString) -> io PFN_vkVoidFunction
- getPhysicalDeviceProperties :: forall io. MonadIO io => PhysicalDevice -> io PhysicalDeviceProperties
- getPhysicalDeviceQueueFamilyProperties :: forall io. MonadIO io => PhysicalDevice -> io ("queueFamilyProperties" ::: Vector QueueFamilyProperties)
- getPhysicalDeviceMemoryProperties :: forall io. MonadIO io => PhysicalDevice -> io PhysicalDeviceMemoryProperties
- getPhysicalDeviceFeatures :: forall io. MonadIO io => PhysicalDevice -> io PhysicalDeviceFeatures
- getPhysicalDeviceFormatProperties :: forall io. MonadIO io => PhysicalDevice -> Format -> io FormatProperties
- getPhysicalDeviceImageFormatProperties :: forall io. MonadIO io => PhysicalDevice -> Format -> ImageType -> ImageTiling -> ImageUsageFlags -> ImageCreateFlags -> io ImageFormatProperties
- data PhysicalDeviceProperties = PhysicalDeviceProperties {}
- data ApplicationInfo = ApplicationInfo {}
- data InstanceCreateInfo (es :: [Type]) = InstanceCreateInfo {}
- data QueueFamilyProperties = QueueFamilyProperties {}
- data PhysicalDeviceMemoryProperties = PhysicalDeviceMemoryProperties {}
- data MemoryType = MemoryType {}
- data MemoryHeap = MemoryHeap {}
- data FormatProperties = FormatProperties {}
- data ImageFormatProperties = ImageFormatProperties {}
- data PhysicalDeviceFeatures = PhysicalDeviceFeatures {- robustBufferAccess :: Bool
- fullDrawIndexUint32 :: Bool
- imageCubeArray :: Bool
- independentBlend :: Bool
- geometryShader :: Bool
- tessellationShader :: Bool
- sampleRateShading :: Bool
- dualSrcBlend :: Bool
- logicOp :: Bool
- multiDrawIndirect :: Bool
- drawIndirectFirstInstance :: Bool
- depthClamp :: Bool
- depthBiasClamp :: Bool
- fillModeNonSolid :: Bool
- depthBounds :: Bool
- wideLines :: Bool
- largePoints :: Bool
- alphaToOne :: Bool
- multiViewport :: Bool
- samplerAnisotropy :: Bool
- textureCompressionETC2 :: Bool
- textureCompressionASTC_LDR :: Bool
- textureCompressionBC :: Bool
- occlusionQueryPrecise :: Bool
- pipelineStatisticsQuery :: Bool
- vertexPipelineStoresAndAtomics :: Bool
- fragmentStoresAndAtomics :: Bool
- shaderTessellationAndGeometryPointSize :: Bool
- shaderImageGatherExtended :: Bool
- shaderStorageImageExtendedFormats :: Bool
- shaderStorageImageMultisample :: Bool
- shaderStorageImageReadWithoutFormat :: Bool
- shaderStorageImageWriteWithoutFormat :: Bool
- shaderUniformBufferArrayDynamicIndexing :: Bool
- shaderSampledImageArrayDynamicIndexing :: Bool
- shaderStorageBufferArrayDynamicIndexing :: Bool
- shaderStorageImageArrayDynamicIndexing :: Bool
- shaderClipDistance :: Bool
- shaderCullDistance :: Bool
- shaderFloat64 :: Bool
- shaderInt64 :: Bool
- shaderInt16 :: Bool
- shaderResourceResidency :: Bool
- shaderResourceMinLod :: Bool
- sparseBinding :: Bool
- sparseResidencyBuffer :: Bool
- sparseResidencyImage2D :: Bool
- sparseResidencyImage3D :: Bool
- sparseResidency2Samples :: Bool
- sparseResidency4Samples :: Bool
- sparseResidency8Samples :: Bool
- sparseResidency16Samples :: Bool
- sparseResidencyAliased :: Bool
- variableMultisampleRate :: Bool
- inheritedQueries :: Bool
 
- data PhysicalDeviceSparseProperties = PhysicalDeviceSparseProperties {}
- data PhysicalDeviceLimits = PhysicalDeviceLimits {- maxImageDimension1D :: Word32
- maxImageDimension2D :: Word32
- maxImageDimension3D :: Word32
- maxImageDimensionCube :: Word32
- maxImageArrayLayers :: Word32
- maxTexelBufferElements :: Word32
- maxUniformBufferRange :: Word32
- maxStorageBufferRange :: Word32
- maxPushConstantsSize :: Word32
- maxMemoryAllocationCount :: Word32
- maxSamplerAllocationCount :: Word32
- bufferImageGranularity :: DeviceSize
- sparseAddressSpaceSize :: DeviceSize
- maxBoundDescriptorSets :: Word32
- maxPerStageDescriptorSamplers :: Word32
- maxPerStageDescriptorUniformBuffers :: Word32
- maxPerStageDescriptorStorageBuffers :: Word32
- maxPerStageDescriptorSampledImages :: Word32
- maxPerStageDescriptorStorageImages :: Word32
- maxPerStageDescriptorInputAttachments :: Word32
- maxPerStageResources :: Word32
- maxDescriptorSetSamplers :: Word32
- maxDescriptorSetUniformBuffers :: Word32
- maxDescriptorSetUniformBuffersDynamic :: Word32
- maxDescriptorSetStorageBuffers :: Word32
- maxDescriptorSetStorageBuffersDynamic :: Word32
- maxDescriptorSetSampledImages :: Word32
- maxDescriptorSetStorageImages :: Word32
- maxDescriptorSetInputAttachments :: Word32
- maxVertexInputAttributes :: Word32
- maxVertexInputBindings :: Word32
- maxVertexInputAttributeOffset :: Word32
- maxVertexInputBindingStride :: Word32
- maxVertexOutputComponents :: Word32
- maxTessellationGenerationLevel :: Word32
- maxTessellationPatchSize :: Word32
- maxTessellationControlPerVertexInputComponents :: Word32
- maxTessellationControlPerVertexOutputComponents :: Word32
- maxTessellationControlPerPatchOutputComponents :: Word32
- maxTessellationControlTotalOutputComponents :: Word32
- maxTessellationEvaluationInputComponents :: Word32
- maxTessellationEvaluationOutputComponents :: Word32
- maxGeometryShaderInvocations :: Word32
- maxGeometryInputComponents :: Word32
- maxGeometryOutputComponents :: Word32
- maxGeometryOutputVertices :: Word32
- maxGeometryTotalOutputComponents :: Word32
- maxFragmentInputComponents :: Word32
- maxFragmentOutputAttachments :: Word32
- maxFragmentDualSrcAttachments :: Word32
- maxFragmentCombinedOutputResources :: Word32
- maxComputeSharedMemorySize :: Word32
- maxComputeWorkGroupCount :: (Word32, Word32, Word32)
- maxComputeWorkGroupInvocations :: Word32
- maxComputeWorkGroupSize :: (Word32, Word32, Word32)
- subPixelPrecisionBits :: Word32
- subTexelPrecisionBits :: Word32
- mipmapPrecisionBits :: Word32
- maxDrawIndexedIndexValue :: Word32
- maxDrawIndirectCount :: Word32
- maxSamplerLodBias :: Float
- maxSamplerAnisotropy :: Float
- maxViewports :: Word32
- maxViewportDimensions :: (Word32, Word32)
- viewportBoundsRange :: (Float, Float)
- viewportSubPixelBits :: Word32
- minMemoryMapAlignment :: Word64
- minTexelBufferOffsetAlignment :: DeviceSize
- minUniformBufferOffsetAlignment :: DeviceSize
- minStorageBufferOffsetAlignment :: DeviceSize
- minTexelOffset :: Int32
- maxTexelOffset :: Word32
- minTexelGatherOffset :: Int32
- maxTexelGatherOffset :: Word32
- minInterpolationOffset :: Float
- maxInterpolationOffset :: Float
- subPixelInterpolationOffsetBits :: Word32
- maxFramebufferWidth :: Word32
- maxFramebufferHeight :: Word32
- maxFramebufferLayers :: Word32
- framebufferColorSampleCounts :: SampleCountFlags
- framebufferDepthSampleCounts :: SampleCountFlags
- framebufferStencilSampleCounts :: SampleCountFlags
- framebufferNoAttachmentsSampleCounts :: SampleCountFlags
- maxColorAttachments :: Word32
- sampledImageColorSampleCounts :: SampleCountFlags
- sampledImageIntegerSampleCounts :: SampleCountFlags
- sampledImageDepthSampleCounts :: SampleCountFlags
- sampledImageStencilSampleCounts :: SampleCountFlags
- storageImageSampleCounts :: SampleCountFlags
- maxSampleMaskWords :: Word32
- timestampComputeAndGraphics :: Bool
- timestampPeriod :: Float
- maxClipDistances :: Word32
- maxCullDistances :: Word32
- maxCombinedClipAndCullDistances :: Word32
- discreteQueuePriorities :: Word32
- pointSizeRange :: (Float, Float)
- lineWidthRange :: (Float, Float)
- pointSizeGranularity :: Float
- lineWidthGranularity :: Float
- strictLines :: Bool
- standardSampleLocations :: Bool
- optimalBufferCopyOffsetAlignment :: DeviceSize
- optimalBufferCopyRowPitchAlignment :: DeviceSize
- nonCoherentAtomSize :: DeviceSize
 
- data Instance = Instance {}
- data PhysicalDevice = PhysicalDevice {}
- data AllocationCallbacks = AllocationCallbacks {}
- newtype InstanceCreateFlags = InstanceCreateFlags Flags
- newtype ImageType where- ImageType Int32
- pattern IMAGE_TYPE_1D :: ImageType
- pattern IMAGE_TYPE_2D :: ImageType
- pattern IMAGE_TYPE_3D :: ImageType
 
- newtype ImageTiling where- ImageTiling Int32
- pattern IMAGE_TILING_OPTIMAL :: ImageTiling
- pattern IMAGE_TILING_LINEAR :: ImageTiling
- pattern IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT :: ImageTiling
 
- newtype InternalAllocationType where
- newtype SystemAllocationScope where- SystemAllocationScope Int32
- pattern SYSTEM_ALLOCATION_SCOPE_COMMAND :: SystemAllocationScope
- pattern SYSTEM_ALLOCATION_SCOPE_OBJECT :: SystemAllocationScope
- pattern SYSTEM_ALLOCATION_SCOPE_CACHE :: SystemAllocationScope
- pattern SYSTEM_ALLOCATION_SCOPE_DEVICE :: SystemAllocationScope
- pattern SYSTEM_ALLOCATION_SCOPE_INSTANCE :: SystemAllocationScope
 
- newtype PhysicalDeviceType where- PhysicalDeviceType Int32
- pattern PHYSICAL_DEVICE_TYPE_OTHER :: PhysicalDeviceType
- pattern PHYSICAL_DEVICE_TYPE_INTEGRATED_GPU :: PhysicalDeviceType
- pattern PHYSICAL_DEVICE_TYPE_DISCRETE_GPU :: PhysicalDeviceType
- pattern PHYSICAL_DEVICE_TYPE_VIRTUAL_GPU :: PhysicalDeviceType
- pattern PHYSICAL_DEVICE_TYPE_CPU :: PhysicalDeviceType
 
- newtype Format where- Format Int32
- pattern FORMAT_UNDEFINED :: Format
- pattern FORMAT_R4G4_UNORM_PACK8 :: Format
- pattern FORMAT_R4G4B4A4_UNORM_PACK16 :: Format
- pattern FORMAT_B4G4R4A4_UNORM_PACK16 :: Format
- pattern FORMAT_R5G6B5_UNORM_PACK16 :: Format
- pattern FORMAT_B5G6R5_UNORM_PACK16 :: Format
- pattern FORMAT_R5G5B5A1_UNORM_PACK16 :: Format
- pattern FORMAT_B5G5R5A1_UNORM_PACK16 :: Format
- pattern FORMAT_A1R5G5B5_UNORM_PACK16 :: Format
- pattern FORMAT_R8_UNORM :: Format
- pattern FORMAT_R8_SNORM :: Format
- pattern FORMAT_R8_USCALED :: Format
- pattern FORMAT_R8_SSCALED :: Format
- pattern FORMAT_R8_UINT :: Format
- pattern FORMAT_R8_SINT :: Format
- pattern FORMAT_R8_SRGB :: Format
- pattern FORMAT_R8G8_UNORM :: Format
- pattern FORMAT_R8G8_SNORM :: Format
- pattern FORMAT_R8G8_USCALED :: Format
- pattern FORMAT_R8G8_SSCALED :: Format
- pattern FORMAT_R8G8_UINT :: Format
- pattern FORMAT_R8G8_SINT :: Format
- pattern FORMAT_R8G8_SRGB :: Format
- pattern FORMAT_R8G8B8_UNORM :: Format
- pattern FORMAT_R8G8B8_SNORM :: Format
- pattern FORMAT_R8G8B8_USCALED :: Format
- pattern FORMAT_R8G8B8_SSCALED :: Format
- pattern FORMAT_R8G8B8_UINT :: Format
- pattern FORMAT_R8G8B8_SINT :: Format
- pattern FORMAT_R8G8B8_SRGB :: Format
- pattern FORMAT_B8G8R8_UNORM :: Format
- pattern FORMAT_B8G8R8_SNORM :: Format
- pattern FORMAT_B8G8R8_USCALED :: Format
- pattern FORMAT_B8G8R8_SSCALED :: Format
- pattern FORMAT_B8G8R8_UINT :: Format
- pattern FORMAT_B8G8R8_SINT :: Format
- pattern FORMAT_B8G8R8_SRGB :: Format
- pattern FORMAT_R8G8B8A8_UNORM :: Format
- pattern FORMAT_R8G8B8A8_SNORM :: Format
- pattern FORMAT_R8G8B8A8_USCALED :: Format
- pattern FORMAT_R8G8B8A8_SSCALED :: Format
- pattern FORMAT_R8G8B8A8_UINT :: Format
- pattern FORMAT_R8G8B8A8_SINT :: Format
- pattern FORMAT_R8G8B8A8_SRGB :: Format
- pattern FORMAT_B8G8R8A8_UNORM :: Format
- pattern FORMAT_B8G8R8A8_SNORM :: Format
- pattern FORMAT_B8G8R8A8_USCALED :: Format
- pattern FORMAT_B8G8R8A8_SSCALED :: Format
- pattern FORMAT_B8G8R8A8_UINT :: Format
- pattern FORMAT_B8G8R8A8_SINT :: Format
- pattern FORMAT_B8G8R8A8_SRGB :: Format
- pattern FORMAT_A8B8G8R8_UNORM_PACK32 :: Format
- pattern FORMAT_A8B8G8R8_SNORM_PACK32 :: Format
- pattern FORMAT_A8B8G8R8_USCALED_PACK32 :: Format
- pattern FORMAT_A8B8G8R8_SSCALED_PACK32 :: Format
- pattern FORMAT_A8B8G8R8_UINT_PACK32 :: Format
- pattern FORMAT_A8B8G8R8_SINT_PACK32 :: Format
- pattern FORMAT_A8B8G8R8_SRGB_PACK32 :: Format
- pattern FORMAT_A2R10G10B10_UNORM_PACK32 :: Format
- pattern FORMAT_A2R10G10B10_SNORM_PACK32 :: Format
- pattern FORMAT_A2R10G10B10_USCALED_PACK32 :: Format
- pattern FORMAT_A2R10G10B10_SSCALED_PACK32 :: Format
- pattern FORMAT_A2R10G10B10_UINT_PACK32 :: Format
- pattern FORMAT_A2R10G10B10_SINT_PACK32 :: Format
- pattern FORMAT_A2B10G10R10_UNORM_PACK32 :: Format
- pattern FORMAT_A2B10G10R10_SNORM_PACK32 :: Format
- pattern FORMAT_A2B10G10R10_USCALED_PACK32 :: Format
- pattern FORMAT_A2B10G10R10_SSCALED_PACK32 :: Format
- pattern FORMAT_A2B10G10R10_UINT_PACK32 :: Format
- pattern FORMAT_A2B10G10R10_SINT_PACK32 :: Format
- pattern FORMAT_R16_UNORM :: Format
- pattern FORMAT_R16_SNORM :: Format
- pattern FORMAT_R16_USCALED :: Format
- pattern FORMAT_R16_SSCALED :: Format
- pattern FORMAT_R16_UINT :: Format
- pattern FORMAT_R16_SINT :: Format
- pattern FORMAT_R16_SFLOAT :: Format
- pattern FORMAT_R16G16_UNORM :: Format
- pattern FORMAT_R16G16_SNORM :: Format
- pattern FORMAT_R16G16_USCALED :: Format
- pattern FORMAT_R16G16_SSCALED :: Format
- pattern FORMAT_R16G16_UINT :: Format
- pattern FORMAT_R16G16_SINT :: Format
- pattern FORMAT_R16G16_SFLOAT :: Format
- pattern FORMAT_R16G16B16_UNORM :: Format
- pattern FORMAT_R16G16B16_SNORM :: Format
- pattern FORMAT_R16G16B16_USCALED :: Format
- pattern FORMAT_R16G16B16_SSCALED :: Format
- pattern FORMAT_R16G16B16_UINT :: Format
- pattern FORMAT_R16G16B16_SINT :: Format
- pattern FORMAT_R16G16B16_SFLOAT :: Format
- pattern FORMAT_R16G16B16A16_UNORM :: Format
- pattern FORMAT_R16G16B16A16_SNORM :: Format
- pattern FORMAT_R16G16B16A16_USCALED :: Format
- pattern FORMAT_R16G16B16A16_SSCALED :: Format
- pattern FORMAT_R16G16B16A16_UINT :: Format
- pattern FORMAT_R16G16B16A16_SINT :: Format
- pattern FORMAT_R16G16B16A16_SFLOAT :: Format
- pattern FORMAT_R32_UINT :: Format
- pattern FORMAT_R32_SINT :: Format
- pattern FORMAT_R32_SFLOAT :: Format
- pattern FORMAT_R32G32_UINT :: Format
- pattern FORMAT_R32G32_SINT :: Format
- pattern FORMAT_R32G32_SFLOAT :: Format
- pattern FORMAT_R32G32B32_UINT :: Format
- pattern FORMAT_R32G32B32_SINT :: Format
- pattern FORMAT_R32G32B32_SFLOAT :: Format
- pattern FORMAT_R32G32B32A32_UINT :: Format
- pattern FORMAT_R32G32B32A32_SINT :: Format
- pattern FORMAT_R32G32B32A32_SFLOAT :: Format
- pattern FORMAT_R64_UINT :: Format
- pattern FORMAT_R64_SINT :: Format
- pattern FORMAT_R64_SFLOAT :: Format
- pattern FORMAT_R64G64_UINT :: Format
- pattern FORMAT_R64G64_SINT :: Format
- pattern FORMAT_R64G64_SFLOAT :: Format
- pattern FORMAT_R64G64B64_UINT :: Format
- pattern FORMAT_R64G64B64_SINT :: Format
- pattern FORMAT_R64G64B64_SFLOAT :: Format
- pattern FORMAT_R64G64B64A64_UINT :: Format
- pattern FORMAT_R64G64B64A64_SINT :: Format
- pattern FORMAT_R64G64B64A64_SFLOAT :: Format
- pattern FORMAT_B10G11R11_UFLOAT_PACK32 :: Format
- pattern FORMAT_E5B9G9R9_UFLOAT_PACK32 :: Format
- pattern FORMAT_D16_UNORM :: Format
- pattern FORMAT_X8_D24_UNORM_PACK32 :: Format
- pattern FORMAT_D32_SFLOAT :: Format
- pattern FORMAT_S8_UINT :: Format
- pattern FORMAT_D16_UNORM_S8_UINT :: Format
- pattern FORMAT_D24_UNORM_S8_UINT :: Format
- pattern FORMAT_D32_SFLOAT_S8_UINT :: Format
- pattern FORMAT_BC1_RGB_UNORM_BLOCK :: Format
- pattern FORMAT_BC1_RGB_SRGB_BLOCK :: Format
- pattern FORMAT_BC1_RGBA_UNORM_BLOCK :: Format
- pattern FORMAT_BC1_RGBA_SRGB_BLOCK :: Format
- pattern FORMAT_BC2_UNORM_BLOCK :: Format
- pattern FORMAT_BC2_SRGB_BLOCK :: Format
- pattern FORMAT_BC3_UNORM_BLOCK :: Format
- pattern FORMAT_BC3_SRGB_BLOCK :: Format
- pattern FORMAT_BC4_UNORM_BLOCK :: Format
- pattern FORMAT_BC4_SNORM_BLOCK :: Format
- pattern FORMAT_BC5_UNORM_BLOCK :: Format
- pattern FORMAT_BC5_SNORM_BLOCK :: Format
- pattern FORMAT_BC6H_UFLOAT_BLOCK :: Format
- pattern FORMAT_BC6H_SFLOAT_BLOCK :: Format
- pattern FORMAT_BC7_UNORM_BLOCK :: Format
- pattern FORMAT_BC7_SRGB_BLOCK :: Format
- pattern FORMAT_ETC2_R8G8B8_UNORM_BLOCK :: Format
- pattern FORMAT_ETC2_R8G8B8_SRGB_BLOCK :: Format
- pattern FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK :: Format
- pattern FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK :: Format
- pattern FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK :: Format
- pattern FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK :: Format
- pattern FORMAT_EAC_R11_UNORM_BLOCK :: Format
- pattern FORMAT_EAC_R11_SNORM_BLOCK :: Format
- pattern FORMAT_EAC_R11G11_UNORM_BLOCK :: Format
- pattern FORMAT_EAC_R11G11_SNORM_BLOCK :: Format
- pattern FORMAT_ASTC_4x4_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_4x4_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_5x4_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_5x4_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_5x5_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_5x5_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_6x5_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_6x5_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_6x6_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_6x6_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_8x5_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_8x5_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_8x6_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_8x6_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_8x8_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_8x8_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_10x5_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_10x5_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_10x6_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_10x6_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_10x8_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_10x8_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_10x10_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_10x10_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_12x10_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_12x10_SRGB_BLOCK :: Format
- pattern FORMAT_ASTC_12x12_UNORM_BLOCK :: Format
- pattern FORMAT_ASTC_12x12_SRGB_BLOCK :: Format
- pattern FORMAT_A4B4G4R4_UNORM_PACK16_EXT :: Format
- pattern FORMAT_A4R4G4B4_UNORM_PACK16_EXT :: Format
- pattern FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT :: Format
- pattern FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG :: Format
- pattern FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG :: Format
- pattern FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG :: Format
- pattern FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG :: Format
- pattern FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG :: Format
- pattern FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG :: Format
- pattern FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG :: Format
- pattern FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG :: Format
- pattern FORMAT_G16_B16_R16_3PLANE_444_UNORM :: Format
- pattern FORMAT_G16_B16R16_2PLANE_422_UNORM :: Format
- pattern FORMAT_G16_B16_R16_3PLANE_422_UNORM :: Format
- pattern FORMAT_G16_B16R16_2PLANE_420_UNORM :: Format
- pattern FORMAT_G16_B16_R16_3PLANE_420_UNORM :: Format
- pattern FORMAT_B16G16R16G16_422_UNORM :: Format
- pattern FORMAT_G16B16G16R16_422_UNORM :: Format
- pattern FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16 :: Format
- pattern FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16 :: Format
- pattern FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16 :: Format
- pattern FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16 :: Format
- pattern FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16 :: Format
- pattern FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16 :: Format
- pattern FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16 :: Format
- pattern FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16 :: Format
- pattern FORMAT_R12X4G12X4_UNORM_2PACK16 :: Format
- pattern FORMAT_R12X4_UNORM_PACK16 :: Format
- pattern FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16 :: Format
- pattern FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16 :: Format
- pattern FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16 :: Format
- pattern FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16 :: Format
- pattern FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16 :: Format
- pattern FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16 :: Format
- pattern FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16 :: Format
- pattern FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16 :: Format
- pattern FORMAT_R10X6G10X6_UNORM_2PACK16 :: Format
- pattern FORMAT_R10X6_UNORM_PACK16 :: Format
- pattern FORMAT_G8_B8_R8_3PLANE_444_UNORM :: Format
- pattern FORMAT_G8_B8R8_2PLANE_422_UNORM :: Format
- pattern FORMAT_G8_B8_R8_3PLANE_422_UNORM :: Format
- pattern FORMAT_G8_B8R8_2PLANE_420_UNORM :: Format
- pattern FORMAT_G8_B8_R8_3PLANE_420_UNORM :: Format
- pattern FORMAT_B8G8R8G8_422_UNORM :: Format
- pattern FORMAT_G8B8G8R8_422_UNORM :: Format
 
- newtype StructureType where- StructureType Int32
- 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_IMAGE_RESOLVE_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_BUFFER_IMAGE_COPY_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_IMAGE_BLIT_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_IMAGE_COPY_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_BUFFER_COPY_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_RESOLVE_IMAGE_INFO_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_BLIT_IMAGE_INFO_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_COPY_IMAGE_TO_BUFFER_INFO_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_COPY_BUFFER_TO_IMAGE_INFO_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_COPY_IMAGE_INFO_2_KHR :: StructureType
- pattern STRUCTURE_TYPE_COPY_BUFFER_INFO_2_KHR :: 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_DEVICE_MEMORY_REPORT_CALLBACK_DATA_EXT :: StructureType
- pattern STRUCTURE_TYPE_DEVICE_DEVICE_MEMORY_REPORT_CREATE_INFO_EXT :: StructureType
- pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_MEMORY_REPORT_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_SHADER_IMAGE_ATOMIC_INT64_FEATURES_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_PHYSICAL_DEVICE_PORTABILITY_SUBSET_PROPERTIES_KHR :: StructureType
- pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PORTABILITY_SUBSET_FEATURES_KHR :: 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
 
- newtype QueueFlagBits where- QueueFlagBits Flags
- pattern QUEUE_GRAPHICS_BIT :: QueueFlagBits
- pattern QUEUE_COMPUTE_BIT :: QueueFlagBits
- pattern QUEUE_TRANSFER_BIT :: QueueFlagBits
- pattern QUEUE_SPARSE_BINDING_BIT :: QueueFlagBits
- pattern QUEUE_PROTECTED_BIT :: QueueFlagBits
 
- type QueueFlags = QueueFlagBits
- newtype MemoryPropertyFlagBits where- MemoryPropertyFlagBits Flags
- pattern MEMORY_PROPERTY_DEVICE_LOCAL_BIT :: MemoryPropertyFlagBits
- pattern MEMORY_PROPERTY_HOST_VISIBLE_BIT :: MemoryPropertyFlagBits
- pattern MEMORY_PROPERTY_HOST_COHERENT_BIT :: MemoryPropertyFlagBits
- pattern MEMORY_PROPERTY_HOST_CACHED_BIT :: MemoryPropertyFlagBits
- pattern MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT :: MemoryPropertyFlagBits
- pattern MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD :: MemoryPropertyFlagBits
- pattern MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD :: MemoryPropertyFlagBits
- pattern MEMORY_PROPERTY_PROTECTED_BIT :: MemoryPropertyFlagBits
 
- type MemoryPropertyFlags = MemoryPropertyFlagBits
- newtype MemoryHeapFlagBits where
- type MemoryHeapFlags = MemoryHeapFlagBits
- newtype ImageUsageFlagBits where- ImageUsageFlagBits Flags
- pattern IMAGE_USAGE_TRANSFER_SRC_BIT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_TRANSFER_DST_BIT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_SAMPLED_BIT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_STORAGE_BIT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_COLOR_ATTACHMENT_BIT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_TRANSIENT_ATTACHMENT_BIT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_INPUT_ATTACHMENT_BIT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_FRAGMENT_DENSITY_MAP_BIT_EXT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_SHADING_RATE_IMAGE_BIT_NV :: ImageUsageFlagBits
 
- type ImageUsageFlags = ImageUsageFlagBits
- newtype ImageCreateFlagBits where- ImageCreateFlagBits Flags
- pattern IMAGE_CREATE_SPARSE_BINDING_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_SPARSE_RESIDENCY_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_SPARSE_ALIASED_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_MUTABLE_FORMAT_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_CUBE_COMPATIBLE_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_SUBSAMPLED_BIT_EXT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_CORNER_SAMPLED_BIT_NV :: ImageCreateFlagBits
- pattern IMAGE_CREATE_DISJOINT_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_PROTECTED_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_EXTENDED_USAGE_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_BLOCK_TEXEL_VIEW_COMPATIBLE_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_ALIAS_BIT :: ImageCreateFlagBits
 
- type ImageCreateFlags = ImageCreateFlagBits
- newtype FormatFeatureFlagBits where- FormatFeatureFlagBits Flags
- pattern FORMAT_FEATURE_SAMPLED_IMAGE_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_STORAGE_IMAGE_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_VERTEX_BUFFER_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_COLOR_ATTACHMENT_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_BLIT_SRC_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_BLIT_DST_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT :: FormatFeatureFlagBits
- 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
- pattern FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_DISJOINT_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_TRANSFER_DST_BIT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_TRANSFER_SRC_BIT :: FormatFeatureFlagBits
 
- type FormatFeatureFlags = FormatFeatureFlagBits
- newtype SampleCountFlagBits where- SampleCountFlagBits Flags
- pattern SAMPLE_COUNT_1_BIT :: SampleCountFlagBits
- pattern SAMPLE_COUNT_2_BIT :: SampleCountFlagBits
- pattern SAMPLE_COUNT_4_BIT :: SampleCountFlagBits
- pattern SAMPLE_COUNT_8_BIT :: SampleCountFlagBits
- pattern SAMPLE_COUNT_16_BIT :: SampleCountFlagBits
- pattern SAMPLE_COUNT_32_BIT :: SampleCountFlagBits
- pattern SAMPLE_COUNT_64_BIT :: SampleCountFlagBits
 
- type SampleCountFlags = SampleCountFlagBits
- type FN_vkInternalAllocationNotification = ("pUserData" ::: Ptr ()) -> CSize -> InternalAllocationType -> SystemAllocationScope -> IO ()
- type PFN_vkInternalAllocationNotification = FunPtr FN_vkInternalAllocationNotification
- type FN_vkInternalFreeNotification = ("pUserData" ::: Ptr ()) -> CSize -> InternalAllocationType -> SystemAllocationScope -> IO ()
- type PFN_vkInternalFreeNotification = FunPtr FN_vkInternalFreeNotification
- type FN_vkReallocationFunction = ("pUserData" ::: Ptr ()) -> ("pOriginal" ::: Ptr ()) -> CSize -> ("alignment" ::: CSize) -> SystemAllocationScope -> IO (Ptr ())
- type PFN_vkReallocationFunction = FunPtr FN_vkReallocationFunction
- type FN_vkAllocationFunction = ("pUserData" ::: Ptr ()) -> CSize -> ("alignment" ::: CSize) -> SystemAllocationScope -> IO (Ptr ())
- type PFN_vkAllocationFunction = FunPtr FN_vkAllocationFunction
- type FN_vkFreeFunction = ("pUserData" ::: Ptr ()) -> ("pMemory" ::: Ptr ()) -> IO ()
- type PFN_vkFreeFunction = FunPtr FN_vkFreeFunction
- type FN_vkVoidFunction = () -> IO ()
- type PFN_vkVoidFunction = FunPtr FN_vkVoidFunction
Documentation
Arguments
| :: forall a io. (Extendss InstanceCreateInfo a, PokeChain a, MonadIO io) | |
| => InstanceCreateInfo a | 
 | 
| -> ("allocator" ::: Maybe AllocationCallbacks) | 
 | 
| -> io Instance | 
vkCreateInstance - Create a new Vulkan instance
Description
createInstance verifies that the requested layers exist. If not,
 createInstance will return
 ERROR_LAYER_NOT_PRESENT. Next
 createInstance verifies that the requested extensions are supported
 (e.g. in the implementation or in any enabled instance layer) and if any
 requested extension is not supported, createInstance must return
 ERROR_EXTENSION_NOT_PRESENT. After
 verifying and enabling the instance layers and extensions the
 Instance object is created and returned to the
 application. If a requested extension is only supported by a layer, both
 the layer and the extension need to be specified at createInstance
 time for the creation to succeed.
Valid Usage
- All
     required extensions
     for each extension in the
     InstanceCreateInfo::ppEnabledExtensionNameslist must also be present in that list
Valid Usage (Implicit)
- pCreateInfomust be a valid pointer to a valid- InstanceCreateInfostructure
- If pAllocatoris notNULL,pAllocatormust be a valid pointer to a validAllocationCallbacksstructure
- pInstancemust be a valid pointer to a- Instancehandle
Return Codes
See Also
withInstance :: forall a io r. (Extendss InstanceCreateInfo a, PokeChain a, MonadIO io) => InstanceCreateInfo a -> Maybe AllocationCallbacks -> (io Instance -> (Instance -> io ()) -> r) -> r Source #
A convenience wrapper to make a compatible pair of calls to
 createInstance and destroyInstance
To ensure that destroyInstance 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.
Arguments
| :: forall io. MonadIO io | |
| => Instance | 
 | 
| -> ("allocator" ::: Maybe AllocationCallbacks) | 
 | 
| -> io () | 
vkDestroyInstance - Destroy an instance of Vulkan
Valid Usage
- All child objects created using instancemust have been destroyed prior to destroyinginstance
- If AllocationCallbackswere provided wheninstancewas created, a compatible set of callbacks must be provided here
- If no AllocationCallbackswere provided wheninstancewas created,pAllocatormust beNULL
Valid Usage (Implicit)
- If instanceis notNULL,instancemust be a validInstancehandle
- If pAllocatoris notNULL,pAllocatormust be a valid pointer to a validAllocationCallbacksstructure
Host Synchronization
- Host access to instancemust be externally synchronized
- Host access to all PhysicalDeviceobjects enumerated frominstancemust be externally synchronized
See Also
enumeratePhysicalDevices Source #
Arguments
| :: forall io. MonadIO io | |
| => Instance | 
 | 
| -> io (Result, "physicalDevices" ::: Vector PhysicalDevice) | 
vkEnumeratePhysicalDevices - Enumerates the physical devices accessible to a Vulkan instance
Description
If pPhysicalDevices is NULL, then the number of physical devices
 available is returned in pPhysicalDeviceCount. Otherwise,
 pPhysicalDeviceCount must point to a variable set by the user to the
 number of elements in the pPhysicalDevices array, and on return the
 variable is overwritten with the number of handles actually written to
 pPhysicalDevices. If pPhysicalDeviceCount is less than the number of
 physical devices available, at most pPhysicalDeviceCount structures
 will be written. If pPhysicalDeviceCount is smaller than the number of
 physical devices available, INCOMPLETE will
 be returned instead of SUCCESS, to indicate
 that not all the available physical devices were returned.
Valid Usage (Implicit)
- instancemust be a valid- Instancehandle
- pPhysicalDeviceCountmust be a valid pointer to a- uint32_tvalue
- If the value referenced by pPhysicalDeviceCountis not0, andpPhysicalDevicesis notNULL,pPhysicalDevicesmust be a valid pointer to an array ofpPhysicalDeviceCountPhysicalDevicehandles
Return Codes
See Also
Arguments
| :: forall io. MonadIO io | |
| => Device | 
 | 
| -> ("name" ::: ByteString) | 
 | 
| -> io PFN_vkVoidFunction | 
vkGetDeviceProcAddr - Return a function pointer for a command
Parameters
The table below defines the various use cases for getDeviceProcAddr
 and expected return value for each case.
Description
The returned function pointer is of type
 PFN_vkVoidFunction, and must be cast to
 the type of the command being queried before use. The function pointer
 must only be called with a dispatchable object (the first parameter)
 that is device or a child of device.
| device | pName | return value | 
|---|---|---|
| NULL | *1 | undefined | 
| invalid device | *1 | undefined | 
| device | NULL | undefined | 
| device | core device-level Vulkan command | fp2 | 
| device | enabled extension device-level commands | fp2 | 
| any other case, not covered above | NULL | 
getDeviceProcAddr behavior
- 1
- "*" means any representable value for the parameter (including
     valid values, invalid values, and NULL).
- 2
- The returned function pointer must only be called with a
     dispatchable object (the first parameter) that is deviceor a child ofdevicee.g.Device,Queue, orCommandBuffer.
Valid Usage (Implicit)
See Also
Arguments
| :: forall io. MonadIO io | |
| => Instance | 
 | 
| -> ("name" ::: ByteString) | 
 | 
| -> io PFN_vkVoidFunction | 
vkGetInstanceProcAddr - Return a function pointer for a command
Description
getInstanceProcAddr itself is obtained in a platform- and loader-
 specific manner. Typically, the loader library will export this command
 as a function symbol, so applications can link against the loader
 library, or load it dynamically and look up the symbol using
 platform-specific APIs.
The table below defines the various use cases for getInstanceProcAddr
 and expected return value (“fp” is “function pointer”) for each case.
The returned function pointer is of type
 PFN_vkVoidFunction, and must be cast to
 the type of the command being queried before use.
| instance | pName | return value | 
|---|---|---|
| *1 | NULL | undefined | 
| invalid non- NULLinstance | *1 | undefined | 
| NULL | getInstanceProcAddr | fp4 | 
| NULL | enumerateInstanceVersion | fp | 
| NULL | enumerateInstanceExtensionProperties | fp | 
| NULL | enumerateInstanceLayerProperties | fp | 
| NULL | createInstance | fp | 
| instance | core Vulkan command | fp2 | 
| instance | enabled instance extension commands for instance | fp2 | 
| instance | available device extension3 commands for instance | fp2 | 
| any other case, not covered above | NULL | 
getInstanceProcAddr behavior
- 1
- "*" means any representable value for the parameter (including
     valid values, invalid values, and NULL).
- 2
- The returned function pointer must only be called with a
     dispatchable object (the first parameter) that is instanceor a child ofinstance, e.g.Instance,PhysicalDevice,Device,Queue, orCommandBuffer.
- 3
- An “available device extension” is a device extension supported by
     any physical device enumerated by instance.
- 4
- Starting with Vulkan 1.2, getInstanceProcAddrcan resolve itself with aNULLinstance pointer.
Valid Usage (Implicit)
- If instanceis notNULL,instancemust be a validInstancehandle
- pNamemust be a null-terminated UTF-8 string
See Also
getPhysicalDeviceProperties Source #
Arguments
| :: forall io. MonadIO io | |
| => PhysicalDevice | 
 
 | 
| -> io PhysicalDeviceProperties | 
vkGetPhysicalDeviceProperties - Returns properties of a physical device
Valid Usage (Implicit)
See Also
getPhysicalDeviceQueueFamilyProperties Source #
Arguments
| :: forall io. MonadIO io | |
| => PhysicalDevice | 
 | 
| -> io ("queueFamilyProperties" ::: Vector QueueFamilyProperties) | 
vkGetPhysicalDeviceQueueFamilyProperties - Reports properties of the queues of the specified physical device
Description
If pQueueFamilyProperties is NULL, then the number of queue families
 available is returned in pQueueFamilyPropertyCount. Implementations
 must support at least one queue family. Otherwise,
 pQueueFamilyPropertyCount must point to a variable set by the user
 to the number of elements in the pQueueFamilyProperties array, and on
 return the variable is overwritten with the number of structures
 actually written to pQueueFamilyProperties. If
 pQueueFamilyPropertyCount is less than the number of queue families
 available, at most pQueueFamilyPropertyCount structures will be
 written.
Valid Usage (Implicit)
- physicalDevicemust be a valid- PhysicalDevicehandle
- pQueueFamilyPropertyCountmust be a valid pointer to a- uint32_tvalue
- If the value referenced by pQueueFamilyPropertyCountis not0, andpQueueFamilyPropertiesis notNULL,pQueueFamilyPropertiesmust be a valid pointer to an array ofpQueueFamilyPropertyCountQueueFamilyPropertiesstructures
See Also
getPhysicalDeviceMemoryProperties Source #
Arguments
| :: forall io. MonadIO io | |
| => PhysicalDevice | 
 
 | 
| -> io PhysicalDeviceMemoryProperties | 
vkGetPhysicalDeviceMemoryProperties - Reports memory information for the specified physical device
Valid Usage (Implicit)
See Also
getPhysicalDeviceFeatures Source #
Arguments
| :: forall io. MonadIO io | |
| => PhysicalDevice | 
 
 | 
| -> io PhysicalDeviceFeatures | 
vkGetPhysicalDeviceFeatures - Reports capabilities of a physical device
Valid Usage (Implicit)
See Also
getPhysicalDeviceFormatProperties Source #
Arguments
| :: forall io. MonadIO io | |
| => PhysicalDevice | 
 
 | 
| -> Format | 
 
 | 
| -> io FormatProperties | 
vkGetPhysicalDeviceFormatProperties - Lists physical device’s format capabilities
Valid Usage (Implicit)
See Also
getPhysicalDeviceImageFormatProperties Source #
Arguments
| :: forall io. MonadIO io | |
| => PhysicalDevice | 
 
 | 
| -> Format | 
 
 | 
| -> ImageType | 
 
 | 
| -> ImageTiling | 
 
 
 | 
| -> ImageUsageFlags | 
 
 
 | 
| -> ImageCreateFlags | 
 
 | 
| -> io ImageFormatProperties | 
vkGetPhysicalDeviceImageFormatProperties - Lists physical device’s image format capabilities
Description
The format, type, tiling, usage, and flags parameters
 correspond to parameters that would be consumed by
 createImage (as members of
 ImageCreateInfo).
If format is not a supported image format, or if the combination of
 format, type, tiling, usage, and flags is not supported for
 images, then getPhysicalDeviceImageFormatProperties returns
 ERROR_FORMAT_NOT_SUPPORTED.
The limitations on an image format that are reported by
 getPhysicalDeviceImageFormatProperties have the following property: if
 usage1 and usage2 of type
 ImageUsageFlags are such that
 the bits set in usage1 are a subset of the bits set in usage2, and
 flags1 and flags2 of type
 ImageCreateFlags are such that
 the bits set in flags1 are a subset of the bits set in flags2, then
 the limitations for usage1 and flags1 must be no more strict than
 the limitations for usage2 and flags2, for all values of format,
 type, and tiling.
Return Codes
See Also
Format,
 ImageCreateFlags,
 ImageFormatProperties, ImageTiling,
 ImageType,
 ImageUsageFlags,
 PhysicalDevice
data PhysicalDeviceProperties Source #
VkPhysicalDeviceProperties - Structure specifying physical device properties
Description
Note
The value of apiVersion may be different than the version returned
 by enumerateInstanceVersion; either
 higher or lower. In such cases, the application must not use
 functionality that exceeds the version of Vulkan associated with a given
 object. The pApiVersion parameter returned by
 enumerateInstanceVersion is the
 version associated with a Instance and its
 children, except for a PhysicalDevice and its
 children. PhysicalDeviceProperties::apiVersion is the version
 associated with a PhysicalDevice and its
 children.
The vendorID and deviceID fields are provided to allow applications
 to adapt to device characteristics that are not adequately exposed by
 other Vulkan queries.
Note
These may include performance profiles, hardware errata, or other characteristics.
The vendor identified by vendorID is the entity responsible for the
 most salient characteristics of the underlying implementation of the
 PhysicalDevice being queried.
Note
For example, in the case of a discrete GPU implementation, this should be the GPU chipset vendor. In the case of a hardware accelerator integrated into a system-on-chip (SoC), this should be the supplier of the silicon IP used to create the accelerator.
If the vendor has a
 PCI vendor ID, the low
 16 bits of vendorID must contain that PCI vendor ID, and the
 remaining bits must be set to zero. Otherwise, the value returned
 must be a valid Khronos vendor ID, obtained as described in the
 Vulkan Documentation and Extensions: Procedures and Conventions
 document in the section “Registering a Vendor ID with Khronos”. Khronos
 vendor IDs are allocated starting at 0x10000, to distinguish them from
 the PCI vendor ID namespace. Khronos vendor IDs are symbolically defined
 in the VendorId type.
The vendor is also responsible for the value returned in deviceID. If
 the implementation is driven primarily by a
 PCI device with a
 PCI device ID, the low 16 bits of deviceID
 must contain that PCI device ID, and the remaining bits must be set
 to zero. Otherwise, the choice of what values to return may be
 dictated by operating system or platform policies - but should
 uniquely identify both the device version and any major configuration
 options (for example, core count in the case of multicore devices).
Note
The same device ID should be used for all physical implementations of that device version and configuration. For example, all uses of a specific silicon IP GPU version and configuration should use the same device ID, even if those uses occur in different SoCs.
See Also
PhysicalDeviceLimits,
 PhysicalDeviceProperties2,
 PhysicalDeviceSparseProperties,
 PhysicalDeviceType,
 getPhysicalDeviceProperties
Constructors
| PhysicalDeviceProperties | |
| Fields 
 | |
Instances
data ApplicationInfo Source #
VkApplicationInfo - Structure specifying application info
Description
Vulkan 1.0 implementations were required to return
 ERROR_INCOMPATIBLE_DRIVER if apiVersion
 was larger than 1.0. Implementations that support Vulkan 1.1 or later
 must not return ERROR_INCOMPATIBLE_DRIVER
 for any value of apiVersion.
Note
Because Vulkan 1.0 implementations may fail with
 ERROR_INCOMPATIBLE_DRIVER, applications
 should determine the version of Vulkan available before calling
 createInstance. If the getInstanceProcAddr returns NULL for
 enumerateInstanceVersion, it is a
 Vulkan 1.0 implementation. Otherwise, the application can call
 enumerateInstanceVersion to
 determine the version of Vulkan.
As long as the instance supports at least Vulkan 1.1, an application can use different versions of Vulkan with an instance than it does with a device or physical device.
Note
The Khronos validation layers will treat apiVersion as the highest API
 version the application targets, and will validate API usage against the
 minimum of that version and the implementation version (instance or
 device, depending on context). If an application tries to use
 functionality from a greater version than this, a validation error will
 be triggered.
For example, if the instance supports Vulkan 1.1 and three physical
 devices support Vulkan 1.0, Vulkan 1.1, and Vulkan 1.2, respectively,
 and if the application sets apiVersion to 1.2, the application can
 use the following versions of Vulkan:
- Vulkan 1.0 can be used with the instance and with all physical devices.
- Vulkan 1.1 can be used with the instance and with the physical devices that support Vulkan 1.1 and Vulkan 1.2.
- Vulkan 1.2 can be used with the physical device that supports Vulkan 1.2.
If we modify the above example so that the application sets apiVersion
 to 1.1, then the application must not use Vulkan 1.2 functionality on
 the physical device that supports Vulkan 1.2.
Implicit layers must be disabled if they do not support a version at
 least as high as apiVersion. See the
 Vulkan Loader Specification and Architecture Overview
 document for additional information.
Note
Providing a NULL InstanceCreateInfo::pApplicationInfo or providing
 an apiVersion of 0 is equivalent to providing an apiVersion of
 VK_MAKE_VERSION(1,0,0).
Valid Usage
- If apiVersionis not0, then it must be greater or equal toAPI_VERSION_1_0
Valid Usage (Implicit)
- sTypemust be- STRUCTURE_TYPE_APPLICATION_INFO
- pNextmust be- NULL
- If pApplicationNameis notNULL,pApplicationNamemust be a null-terminated UTF-8 string
- If pEngineNameis notNULL,pEngineNamemust be a null-terminated UTF-8 string
See Also
Constructors
| ApplicationInfo | |
| Fields 
 | |
Instances
data InstanceCreateInfo (es :: [Type]) Source #
VkInstanceCreateInfo - Structure specifying parameters of a newly created instance
Valid Usage (Implicit)
- sTypemust be- STRUCTURE_TYPE_INSTANCE_CREATE_INFO
- Each pNextmember of any structure (including this one) in thepNextchain must be eitherNULLor a pointer to a valid instance ofDebugReportCallbackCreateInfoEXT,DebugUtilsMessengerCreateInfoEXT,ValidationFeaturesEXT, orValidationFlagsEXT
- The sTypevalue of each struct in thepNextchain must be unique, with the exception of structures of typeDebugUtilsMessengerCreateInfoEXT
- flagsmust be- 0
- If pApplicationInfois notNULL,pApplicationInfomust be a valid pointer to a validApplicationInfostructure
- If enabledLayerCountis not0,ppEnabledLayerNamesmust be a valid pointer to an array ofenabledLayerCountnull-terminated UTF-8 strings
- If enabledExtensionCountis not0,ppEnabledExtensionNamesmust be a valid pointer to an array ofenabledExtensionCountnull-terminated UTF-8 strings
See Also
ApplicationInfo,
 InstanceCreateFlags,
 StructureType, createInstance
Constructors
| InstanceCreateInfo | |
| Fields 
 | |
Instances
data QueueFamilyProperties Source #
VkQueueFamilyProperties - Structure providing information about a queue family
Description
The value returned in minImageTransferGranularity has a unit of
 compressed texel blocks for images having a block-compressed format, and
 a unit of texels otherwise.
Possible values of minImageTransferGranularity are:
- (0,0,0) which indicates that only whole mip levels must be transferred using the image transfer operations on the corresponding queues. In this case, the following restrictions apply to all offset and extent parameters of image transfer operations: 
- (Ax, Ay, Az) where Ax, Ay, and Az are all integer powers of two. In this case the following restrictions apply to all image transfer operations: - x,- y, and- zof a- Offset3Dparameter must be integer multiples of Ax, Ay, and Az, respectively.
- widthof a- Extent3Dparameter must be an integer multiple of Ax, or else- x+- widthmust equal the width of the image subresource corresponding to the parameter.
- heightof a- Extent3Dparameter must be an integer multiple of Ay, or else- y+- heightmust equal the height of the image subresource corresponding to the parameter.
- depthof a- Extent3Dparameter must be an integer multiple of Az, or else- z+- depthmust equal the depth of the image subresource corresponding to the parameter.
- If the format of the image corresponding to the parameters is one of the block-compressed formats then for the purposes of the above calculations the granularity must be scaled up by the compressed texel block dimensions.
 
Queues supporting graphics and/or compute operations must report
 (1,1,1) in minImageTransferGranularity, meaning that there are no
 additional restrictions on the granularity of image transfer operations
 for these queues. Other queues supporting image transfer operations are
 only required to support whole mip level transfers, thus
 minImageTransferGranularity for queues belonging to such queue
 families may be (0,0,0).
The Device Memory section describes memory properties queried from the physical device.
For physical device feature queries see the Features chapter.
See Also
Extent3D,
 QueueFamilyProperties2,
 QueueFlags,
 getPhysicalDeviceQueueFamilyProperties
Constructors
| QueueFamilyProperties | |
| Fields 
 | |
Instances
data PhysicalDeviceMemoryProperties Source #
VkPhysicalDeviceMemoryProperties - Structure specifying physical device memory properties
Description
The PhysicalDeviceMemoryProperties structure describes a number of
 memory heaps as well as a number of memory types that can be used
 to access memory allocated in those heaps. Each heap describes a memory
 resource of a particular size, and each memory type describes a set of
 memory properties (e.g. host cached vs uncached) that can be used with
 a given memory heap. Allocations using a particular memory type will
 consume resources from the heap indicated by that memory type’s heap
 index. More than one memory type may share each heap, and the heaps
 and memory types provide a mechanism to advertise an accurate size of
 the physical memory resources while allowing the memory to be used with
 a variety of different properties.
The number of memory heaps is given by memoryHeapCount and is less
 than or equal to MAX_MEMORY_HEAPS. Each
 heap is described by an element of the memoryHeaps array as a
 MemoryHeap structure. The number of memory types available across all
 memory heaps is given by memoryTypeCount and is less than or equal to
 MAX_MEMORY_TYPES. Each memory type is
 described by an element of the memoryTypes array as a MemoryType
 structure.
At least one heap must include
 MEMORY_HEAP_DEVICE_LOCAL_BIT in
 MemoryHeap::flags. If there are multiple heaps that all have similar
 performance characteristics, they may all include
 MEMORY_HEAP_DEVICE_LOCAL_BIT.
 In a unified memory architecture (UMA) system there is often only a
 single memory heap which is considered to be equally “local” to the host
 and to the device, and such an implementation must advertise the heap
 as device-local.
Each memory type returned by getPhysicalDeviceMemoryProperties must
 have its propertyFlags set to one of the following values:
- 0
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT
- MEMORY_PROPERTY_PROTECTED_BIT
- MEMORY_PROPERTY_PROTECTED_BIT|- MEMORY_PROPERTY_DEVICE_LOCAL_BIT
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
There must be at least one memory type with both the
 MEMORY_PROPERTY_HOST_VISIBLE_BIT
 and
 MEMORY_PROPERTY_HOST_COHERENT_BIT
 bits set in its propertyFlags. There must be at least one memory
 type with the
 MEMORY_PROPERTY_DEVICE_LOCAL_BIT
 bit set in its propertyFlags. If the
 deviceCoherentMemory
 feature is enabled, there must be at least one memory type with the
 MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
 bit set in its propertyFlags.
For each pair of elements X and Y returned in memoryTypes,
 X must be placed at a lower index position than Y if:
- the set of bit flags returned in the propertyFlagsmember of X is a strict subset of the set of bit flags returned in thepropertyFlagsmember of Y; or
- the propertyFlagsmembers of X and Y are equal, and X belongs to a memory heap with greater performance (as determined in an implementation-specific manner) ; or
- the propertyFlagsmembers of Y includesMEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMDorMEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMDand X does not
Note
There is no ordering requirement between X and Y elements for
 the case their propertyFlags members are not in a subset relation.
 That potentially allows more than one possible way to order the same set
 of memory types. Notice that the
 list of all allowed memory property flag combinations
 is written in a valid order. But if instead
 MEMORY_PROPERTY_DEVICE_LOCAL_BIT
 was before
 MEMORY_PROPERTY_HOST_VISIBLE_BIT
 |
 MEMORY_PROPERTY_HOST_COHERENT_BIT,
 the list would still be in a valid order.
There may be a performance penalty for using device coherent or uncached device memory types, and using these accidentally is undesirable. In order to avoid this, memory types with these properties always appear at the end of the list; but are subject to the same rules otherwise.
This ordering requirement enables applications to use a simple search loop to select the desired memory type along the lines of:
// Find a memory in `memoryTypeBitsRequirement` that includes all of `requiredProperties`
int32_t findProperties(const VkPhysicalDeviceMemoryProperties* pMemoryProperties,
                       uint32_t memoryTypeBitsRequirement,
                       VkMemoryPropertyFlags requiredProperties) {
    const uint32_t memoryCount = pMemoryProperties->memoryTypeCount;
    for (uint32_t memoryIndex = 0; memoryIndex < memoryCount; ++memoryIndex) {
        const uint32_t memoryTypeBits = (1 << memoryIndex);
        const bool isRequiredMemoryType = memoryTypeBitsRequirement & memoryTypeBits;
        const VkMemoryPropertyFlags properties =
            pMemoryProperties->memoryTypes[memoryIndex].propertyFlags;
        const bool hasRequiredProperties =
            (properties & requiredProperties) == requiredProperties;
        if (isRequiredMemoryType && hasRequiredProperties)
            return static_cast<int32_t>(memoryIndex);
    }
    // failed to find memory type
    return -1;
}
// Try to find an optimal memory type, or if it does not exist try fallback memory type
// `device` is the VkDevice
// `image` is the VkImage that requires memory to be bound
// `memoryProperties` properties as returned by vkGetPhysicalDeviceMemoryProperties
// `requiredProperties` are the property flags that must be present
// `optimalProperties` are the property flags that are preferred by the application
VkMemoryRequirements memoryRequirements;
vkGetImageMemoryRequirements(device, image, &memoryRequirements);
int32_t memoryType =
    findProperties(&memoryProperties, memoryRequirements.memoryTypeBits, optimalProperties);
if (memoryType == -1) // not found; try fallback properties
    memoryType =
        findProperties(&memoryProperties, memoryRequirements.memoryTypeBits, requiredProperties);See Also
MemoryHeap, MemoryType,
 PhysicalDeviceMemoryProperties2,
 getPhysicalDeviceMemoryProperties
Constructors
| PhysicalDeviceMemoryProperties | |
| Fields 
 | |
Instances
data MemoryType Source #
VkMemoryType - Structure specifying memory type
See Also
Constructors
| MemoryType | |
| Fields 
 | |
Instances
data MemoryHeap Source #
VkMemoryHeap - Structure specifying a memory heap
See Also
Constructors
| MemoryHeap | |
| Fields 
 | |
Instances
data FormatProperties Source #
VkFormatProperties - Structure specifying image format properties
Description
Note
If no format feature flags are supported, the format itself is not supported, and images of that format cannot be created.
If format is a block-compressed format, then bufferFeatures must
 not support any features for the format.
If format is not a multi-plane format then linearTilingFeatures and
 optimalTilingFeatures must not contain
 FORMAT_FEATURE_DISJOINT_BIT.
See Also
FormatFeatureFlags,
 FormatProperties2,
 getPhysicalDeviceFormatProperties
Constructors
| FormatProperties | |
| Fields 
 | |
Instances
data ImageFormatProperties Source #
VkImageFormatProperties - Structure specifying an image format properties
Members
- maxExtentare the maximum image dimensions. See the Allowed Extent Values section below for how these values are constrained by- type.
- maxMipLevelsis the maximum number of mipmap levels.- maxMipLevelsmust be equal to the number of levels in the complete mipmap chain based on the- maxExtent.width,- maxExtent.height, and- maxExtent.depth, except when one of the following conditions is true, in which case it may instead be- 1:- getPhysicalDeviceImageFormatProperties::- tilingwas- IMAGE_TILING_LINEAR
- PhysicalDeviceImageFormatInfo2::- tilingwas- IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT
- the
    PhysicalDeviceImageFormatInfo2::pNextchain included aPhysicalDeviceExternalImageFormatInfostructure with a handle type included in thehandleTypesmember for which mipmap image support is not required
- image formatis one of those listed in https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion
- flagscontains- IMAGE_CREATE_SUBSAMPLED_BIT_EXT
 
- maxArrayLayersis the maximum number of array layers.- maxArrayLayersmust be no less than- PhysicalDeviceLimits::- maxImageArrayLayers, except when one of the following conditions is true, in which case it may instead be- 1:- tilingis- IMAGE_TILING_LINEAR
- tilingis- IMAGE_TILING_OPTIMALand- typeis- IMAGE_TYPE_3D
- formatis one of those listed in https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion
 
- If tilingisIMAGE_TILING_DRM_FORMAT_MODIFIER_EXT, thenmaxArrayLayersmust not be 0.
- sampleCountsis a bitmask of- SampleCountFlagBitsspecifying all the supported sample counts for this image as described below.
- maxResourceSizeis an upper bound on the total image size in bytes, inclusive of all image subresources. Implementations may have an address space limit on total size of a resource, which is advertised by this property.- maxResourceSizemust be at least 231.
Description
Note
There is no mechanism to query the size of an image before creating it,
 to compare that size against maxResourceSize. If an application
 attempts to create an image that exceeds this limit, the creation will
 fail and createImage will return
 ERROR_OUT_OF_DEVICE_MEMORY. While the
 advertised limit must be at least 231, it may not be possible to
 create an image that approaches that size, particularly for
 IMAGE_TYPE_1D.
If the combination of parameters to
 getPhysicalDeviceImageFormatProperties is not supported by the
 implementation for use in createImage, then all
 members of ImageFormatProperties will be filled with zero.
Note
Filling ImageFormatProperties with zero for unsupported formats is an
 exception to the usual rule that output structures have undefined
 contents on error. This exception was unintentional, but is preserved
 for backwards compatibility.
See Also
DeviceSize,
 Extent3D,
 ExternalImageFormatPropertiesNV,
 ImageFormatProperties2,
 SampleCountFlags,
 getPhysicalDeviceImageFormatProperties
Constructors
| ImageFormatProperties | |
| Fields | |
Instances
data PhysicalDeviceFeatures Source #
VkPhysicalDeviceFeatures - Structure describing the fine-grained features that can be supported by an implementation
Members
The members of the PhysicalDeviceFeatures structure describe the
 following features:
See Also
Bool32,
 DeviceCreateInfo,
 PhysicalDeviceFeatures2,
 getPhysicalDeviceFeatures
Constructors
| PhysicalDeviceFeatures | |
| Fields 
 | |
Instances
data PhysicalDeviceSparseProperties Source #
VkPhysicalDeviceSparseProperties - Structure specifying physical device sparse memory properties
See Also
Constructors
| PhysicalDeviceSparseProperties | |
| Fields 
 | |
Instances
data PhysicalDeviceLimits Source #
VkPhysicalDeviceLimits - Structure reporting implementation-dependent physical device limits
Members
The PhysicalDeviceLimits are properties of the physical device. These
 are available in the limits member of the PhysicalDeviceProperties
 structure which is returned from getPhysicalDeviceProperties.
Description
- 1
- For all bitmasks of
     SampleCountFlagBits, the sample count limits defined above represent the minimum supported sample counts for each image type. Individual images may support additional sample counts, which are queried usinggetPhysicalDeviceImageFormatPropertiesas described in Supported Sample Counts.
See Also
Bool32,
 DeviceSize, PhysicalDeviceProperties,
 SampleCountFlags
Constructors
| PhysicalDeviceLimits | |
| Fields 
 | |
Instances
VkInstance - Opaque handle to an instance object
See Also
createAndroidSurfaceKHR,
 createDebugReportCallbackEXT,
 createDebugUtilsMessengerEXT,
 createDirectFBSurfaceEXT,
 createDisplayPlaneSurfaceKHR,
 createHeadlessSurfaceEXT,
 createIOSSurfaceMVK,
 createImagePipeSurfaceFUCHSIA,
 createInstance,
 createMacOSSurfaceMVK,
 createMetalSurfaceEXT,
 createStreamDescriptorSurfaceGGP,
 createViSurfaceNN,
 createWaylandSurfaceKHR,
 createWin32SurfaceKHR,
 createXcbSurfaceKHR,
 createXlibSurfaceKHR,
 debugReportMessageEXT,
 destroyDebugReportCallbackEXT,
 destroyDebugUtilsMessengerEXT,
 destroyInstance,
 destroySurfaceKHR,
 enumeratePhysicalDeviceGroups,
 enumeratePhysicalDeviceGroupsKHR,
 enumeratePhysicalDevices,
 getInstanceProcAddr,
 submitDebugUtilsMessageEXT
Constructors
| Instance | |
| Fields | |
Instances
| Eq Instance Source # | |
| Show Instance Source # | |
| Zero Instance Source # | |
| Defined in Vulkan.Core10.Handles | |
| HasObjectType Instance Source # | |
| Defined in Vulkan.Core10.Handles Methods objectTypeAndHandle :: Instance -> (ObjectType, Word64) Source # | |
| IsHandle Instance Source # | |
| Defined in Vulkan.Core10.Handles | |
data PhysicalDevice Source #
VkPhysicalDevice - Opaque handle to a physical device object
See Also
DeviceGroupDeviceCreateInfo,
 PhysicalDeviceGroupProperties,
 acquireXlibDisplayEXT,
 createDevice,
 createDisplayModeKHR,
 enumerateDeviceExtensionProperties,
 enumerateDeviceLayerProperties,
 enumeratePhysicalDeviceQueueFamilyPerformanceQueryCountersKHR,
 enumeratePhysicalDevices,
 getDisplayModeProperties2KHR,
 getDisplayModePropertiesKHR,
 getDisplayPlaneCapabilities2KHR,
 getDisplayPlaneCapabilitiesKHR,
 getDisplayPlaneSupportedDisplaysKHR,
 getPhysicalDeviceCalibrateableTimeDomainsEXT,
 getPhysicalDeviceCooperativeMatrixPropertiesNV,
 getPhysicalDeviceDirectFBPresentationSupportEXT,
 getPhysicalDeviceDisplayPlaneProperties2KHR,
 getPhysicalDeviceDisplayPlanePropertiesKHR,
 getPhysicalDeviceDisplayProperties2KHR,
 getPhysicalDeviceDisplayPropertiesKHR,
 getPhysicalDeviceExternalBufferProperties,
 getPhysicalDeviceExternalBufferPropertiesKHR,
 getPhysicalDeviceExternalFenceProperties,
 getPhysicalDeviceExternalFencePropertiesKHR,
 getPhysicalDeviceExternalImageFormatPropertiesNV,
 getPhysicalDeviceExternalSemaphoreProperties,
 getPhysicalDeviceExternalSemaphorePropertiesKHR,
 getPhysicalDeviceFeatures,
 getPhysicalDeviceFeatures2,
 getPhysicalDeviceFeatures2KHR,
 getPhysicalDeviceFormatProperties,
 getPhysicalDeviceFormatProperties2,
 getPhysicalDeviceFormatProperties2KHR,
 getPhysicalDeviceImageFormatProperties,
 getPhysicalDeviceImageFormatProperties2,
 getPhysicalDeviceImageFormatProperties2KHR,
 getPhysicalDeviceMemoryProperties,
 getPhysicalDeviceMemoryProperties2,
 getPhysicalDeviceMemoryProperties2KHR,
 getPhysicalDeviceMultisamplePropertiesEXT,
 getPhysicalDevicePresentRectanglesKHR,
 getPhysicalDeviceProperties,
 getPhysicalDeviceProperties2,
 getPhysicalDeviceProperties2KHR,
 getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR,
 getPhysicalDeviceQueueFamilyProperties,
 getPhysicalDeviceQueueFamilyProperties2,
 getPhysicalDeviceQueueFamilyProperties2KHR,
 getPhysicalDeviceSparseImageFormatProperties,
 getPhysicalDeviceSparseImageFormatProperties2,
 getPhysicalDeviceSparseImageFormatProperties2KHR,
 getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV,
 getPhysicalDeviceSurfaceCapabilities2EXT,
 getPhysicalDeviceSurfaceCapabilities2KHR,
 getPhysicalDeviceSurfaceCapabilitiesKHR,
 getPhysicalDeviceSurfaceFormats2KHR,
 getPhysicalDeviceSurfaceFormatsKHR,
 getPhysicalDeviceSurfacePresentModes2EXT,
 getPhysicalDeviceSurfacePresentModesKHR,
 getPhysicalDeviceSurfaceSupportKHR,
 getPhysicalDeviceToolPropertiesEXT,
 getPhysicalDeviceWaylandPresentationSupportKHR,
 getPhysicalDeviceWin32PresentationSupportKHR,
 getPhysicalDeviceXcbPresentationSupportKHR,
 getPhysicalDeviceXlibPresentationSupportKHR,
 getRandROutputDisplayEXT,
 releaseDisplayEXT
Constructors
| PhysicalDevice | |
| Fields | |
Instances
| Eq PhysicalDevice Source # | |
| Defined in Vulkan.Core10.Handles Methods (==) :: PhysicalDevice -> PhysicalDevice -> Bool # (/=) :: PhysicalDevice -> PhysicalDevice -> Bool # | |
| Show PhysicalDevice Source # | |
| Defined in Vulkan.Core10.Handles Methods showsPrec :: Int -> PhysicalDevice -> ShowS # show :: PhysicalDevice -> String # showList :: [PhysicalDevice] -> ShowS # | |
| Zero PhysicalDevice Source # | |
| Defined in Vulkan.Core10.Handles Methods | |
| HasObjectType PhysicalDevice Source # | |
| Defined in Vulkan.Core10.Handles Methods objectTypeAndHandle :: PhysicalDevice -> (ObjectType, Word64) Source # | |
| IsHandle PhysicalDevice Source # | |
| Defined in Vulkan.Core10.Handles | |
data AllocationCallbacks Source #
VkAllocationCallbacks - Structure containing callback function pointers for memory allocation
Valid Usage
- pfnAllocationmust be a valid pointer to a valid user-defined- PFN_vkAllocationFunction
- pfnReallocationmust be a valid pointer to a valid user-defined- PFN_vkReallocationFunction
- pfnFreemust be a valid pointer to a valid user-defined- PFN_vkFreeFunction
- If either of pfnInternalAllocationorpfnInternalFreeis notNULL, both must be valid callbacks
See Also
PFN_vkAllocationFunction,
 PFN_vkFreeFunction,
 PFN_vkInternalAllocationNotification,
 PFN_vkInternalFreeNotification,
 PFN_vkReallocationFunction,
 allocateMemory,
 createAccelerationStructureKHR,
 createAccelerationStructureNV,
 createAndroidSurfaceKHR,
 createBuffer,
 createBufferView,
 createCommandPool,
 createComputePipelines,
 createDebugReportCallbackEXT,
 createDebugUtilsMessengerEXT,
 createDeferredOperationKHR,
 createDescriptorPool,
 createDescriptorSetLayout,
 createDescriptorUpdateTemplate,
 createDescriptorUpdateTemplateKHR,
 createDevice,
 createDirectFBSurfaceEXT,
 createDisplayModeKHR,
 createDisplayPlaneSurfaceKHR,
 createEvent, createFence,
 createFramebuffer,
 createGraphicsPipelines,
 createHeadlessSurfaceEXT,
 createIOSSurfaceMVK,
 createImage,
 createImagePipeSurfaceFUCHSIA,
 createImageView,
 createIndirectCommandsLayoutNV,
 createInstance,
 createMacOSSurfaceMVK,
 createMetalSurfaceEXT,
 createPipelineCache,
 createPipelineLayout,
 createPrivateDataSlotEXT,
 createQueryPool,
 createRayTracingPipelinesKHR,
 createRayTracingPipelinesNV,
 createRenderPass,
 createRenderPass2,
 createRenderPass2KHR,
 createSampler,
 createSamplerYcbcrConversion,
 createSamplerYcbcrConversionKHR,
 createSemaphore,
 createShaderModule,
 createSharedSwapchainsKHR,
 createStreamDescriptorSurfaceGGP,
 createSwapchainKHR,
 createValidationCacheEXT,
 createViSurfaceNN,
 createWaylandSurfaceKHR,
 createWin32SurfaceKHR,
 createXcbSurfaceKHR,
 createXlibSurfaceKHR,
 destroyAccelerationStructureKHR,
 destroyAccelerationStructureNV,
 destroyBuffer,
 destroyBufferView,
 destroyCommandPool,
 destroyDebugReportCallbackEXT,
 destroyDebugUtilsMessengerEXT,
 destroyDeferredOperationKHR,
 destroyDescriptorPool,
 destroyDescriptorSetLayout,
 destroyDescriptorUpdateTemplate,
 destroyDescriptorUpdateTemplateKHR,
 destroyDevice,
 destroyEvent, destroyFence,
 destroyFramebuffer,
 destroyImage,
 destroyImageView,
 destroyIndirectCommandsLayoutNV,
 destroyInstance,
 destroyPipeline,
 destroyPipelineCache,
 destroyPipelineLayout,
 destroyPrivateDataSlotEXT,
 destroyQueryPool,
 destroyRenderPass,
 destroySampler,
 destroySamplerYcbcrConversion,
 destroySamplerYcbcrConversionKHR,
 destroySemaphore,
 destroyShaderModule,
 destroySurfaceKHR,
 destroySwapchainKHR,
 destroyValidationCacheEXT,
 freeMemory,
 registerDeviceEventEXT,
 registerDisplayEventEXT
Constructors
| AllocationCallbacks | |
| Fields 
 | |
Instances
newtype InstanceCreateFlags Source #
VkInstanceCreateFlags - Reserved for future use
Description
InstanceCreateFlags is a bitmask type for setting a mask, but is
 currently reserved for future use.
See Also
Constructors
| InstanceCreateFlags Flags | 
Instances
VkImageType - Specifies the type of an image object
See Also
ImageCreateInfo,
 PhysicalDeviceImageFormatInfo2,
 PhysicalDeviceSparseImageFormatInfo2,
 getPhysicalDeviceExternalImageFormatPropertiesNV,
 getPhysicalDeviceImageFormatProperties,
 getPhysicalDeviceSparseImageFormatProperties
Bundled Patterns
| pattern IMAGE_TYPE_1D :: ImageType | 
 | 
| pattern IMAGE_TYPE_2D :: ImageType | 
 | 
| pattern IMAGE_TYPE_3D :: ImageType | 
 | 
Instances
| Eq ImageType Source # | |
| Ord ImageType Source # | |
| Read ImageType Source # | |
| Show ImageType Source # | |
| Storable ImageType Source # | |
| Defined in Vulkan.Core10.Enums.ImageType | |
| Zero ImageType Source # | |
| Defined in Vulkan.Core10.Enums.ImageType | |
newtype ImageTiling Source #
VkImageTiling - Specifies the tiling arrangement of data in an image
See Also
ImageCreateInfo,
 PhysicalDeviceImageFormatInfo2,
 PhysicalDeviceSparseImageFormatInfo2,
 getPhysicalDeviceExternalImageFormatPropertiesNV,
 getPhysicalDeviceImageFormatProperties,
 getPhysicalDeviceSparseImageFormatProperties
Constructors
| ImageTiling Int32 | 
Bundled Patterns
| pattern IMAGE_TILING_OPTIMAL :: ImageTiling | 
 | 
| pattern IMAGE_TILING_LINEAR :: ImageTiling | 
 | 
| pattern IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT :: ImageTiling | 
 | 
Instances
newtype InternalAllocationType Source #
VkInternalAllocationType - Allocation type
See Also
PFN_vkInternalAllocationNotification,
 PFN_vkInternalFreeNotification
Constructors
| InternalAllocationType Int32 | 
Bundled Patterns
| pattern INTERNAL_ALLOCATION_TYPE_EXECUTABLE :: InternalAllocationType | 
 | 
Instances
newtype SystemAllocationScope Source #
VkSystemAllocationScope - Allocation scope
Description
- SYSTEM_ALLOCATION_SCOPE_COMMANDspecifies that the allocation is scoped to the duration of the Vulkan command.
- SYSTEM_ALLOCATION_SCOPE_OBJECTspecifies that the allocation is scoped to the lifetime of the Vulkan object that is being created or used.
- SYSTEM_ALLOCATION_SCOPE_CACHEspecifies that the allocation is scoped to the lifetime of a- PipelineCacheor- ValidationCacheEXTobject.
- SYSTEM_ALLOCATION_SCOPE_DEVICEspecifies that the allocation is scoped to the lifetime of the Vulkan device.
- SYSTEM_ALLOCATION_SCOPE_INSTANCEspecifies that the allocation is scoped to the lifetime of the Vulkan instance.
Most Vulkan commands operate on a single object, or there is a sole
 object that is being created or manipulated. When an allocation uses an
 allocation scope of SYSTEM_ALLOCATION_SCOPE_OBJECT or
 SYSTEM_ALLOCATION_SCOPE_CACHE, the allocation is scoped to the object
 being created or manipulated.
When an implementation requires host memory, it will make callbacks to the application using the most specific allocator and allocation scope available:
- If an allocation is scoped to the duration of a command, the
     allocator will use the SYSTEM_ALLOCATION_SCOPE_COMMANDallocation scope. The most specific allocator available is used: if the object being created or manipulated has an allocator, that object’s allocator will be used, else if the parentDevicehas an allocator it will be used, else if the parentInstancehas an allocator it will be used. Else,
- If an allocation is associated with a
     ValidationCacheEXTorPipelineCacheobject, the allocator will use theSYSTEM_ALLOCATION_SCOPE_CACHEallocation scope. The most specific allocator available is used (cache, else device, else instance). Else,
- If an allocation is scoped to the lifetime of an object, that object
     is being created or manipulated by the command, and that object’s
     type is not DeviceorInstance, the allocator will use an allocation scope ofSYSTEM_ALLOCATION_SCOPE_OBJECT. The most specific allocator available is used (object, else device, else instance). Else,
- If an allocation is scoped to the lifetime of a device, the
     allocator will use an allocation scope of
     SYSTEM_ALLOCATION_SCOPE_DEVICE. The most specific allocator available is used (device, else instance). Else,
- If the allocation is scoped to the lifetime of an instance and the
     instance has an allocator, its allocator will be used with an
     allocation scope of SYSTEM_ALLOCATION_SCOPE_INSTANCE.
- Otherwise an implementation will allocate memory through an alternative mechanism that is unspecified.
See Also
Constructors
| SystemAllocationScope Int32 | 
Bundled Patterns
Instances
newtype PhysicalDeviceType Source #
VkPhysicalDeviceType - Supported physical device types
Description
The physical device type is advertised for informational purposes only, and does not directly affect the operation of the system. However, the device type may correlate with other advertised properties or capabilities of the system, such as how many memory heaps there are.
See Also
Constructors
| PhysicalDeviceType Int32 | 
Bundled Patterns
| pattern PHYSICAL_DEVICE_TYPE_OTHER :: PhysicalDeviceType | 
 | 
| pattern PHYSICAL_DEVICE_TYPE_INTEGRATED_GPU :: PhysicalDeviceType | 
 | 
| pattern PHYSICAL_DEVICE_TYPE_DISCRETE_GPU :: PhysicalDeviceType | 
 | 
| pattern PHYSICAL_DEVICE_TYPE_VIRTUAL_GPU :: PhysicalDeviceType | 
 | 
| pattern PHYSICAL_DEVICE_TYPE_CPU :: PhysicalDeviceType | 
 | 
Instances
VkFormat - Available image formats
See Also
AccelerationStructureCreateGeometryTypeInfoKHR,
 AccelerationStructureGeometryTrianglesDataKHR,
 AndroidHardwareBufferFormatPropertiesANDROID,
 AttachmentDescription,
 AttachmentDescription2,
 BufferViewCreateInfo,
 FramebufferAttachmentImageInfo,
 GeometryTrianglesNV,
 ImageCreateInfo,
 ImageFormatListCreateInfo,
 ImageViewASTCDecodeModeEXT,
 ImageViewCreateInfo,
 PhysicalDeviceImageFormatInfo2,
 PhysicalDeviceSparseImageFormatInfo2,
 SamplerCustomBorderColorCreateInfoEXT,
 SamplerYcbcrConversionCreateInfo,
 SurfaceFormatKHR,
 SwapchainCreateInfoKHR,
 VertexInputAttributeDescription,
 getPhysicalDeviceExternalImageFormatPropertiesNV,
 getPhysicalDeviceFormatProperties,
 getPhysicalDeviceFormatProperties2,
 getPhysicalDeviceFormatProperties2KHR,
 getPhysicalDeviceImageFormatProperties,
 getPhysicalDeviceSparseImageFormatProperties
Bundled Patterns
| pattern FORMAT_UNDEFINED :: Format | 
 | 
| pattern FORMAT_R4G4_UNORM_PACK8 :: Format | 
 | 
| pattern FORMAT_R4G4B4A4_UNORM_PACK16 :: Format | 
 | 
| pattern FORMAT_B4G4R4A4_UNORM_PACK16 :: Format | 
 | 
| pattern FORMAT_R5G6B5_UNORM_PACK16 :: Format | 
 | 
| pattern FORMAT_B5G6R5_UNORM_PACK16 :: Format | 
 | 
| pattern FORMAT_R5G5B5A1_UNORM_PACK16 :: Format | 
 | 
| pattern FORMAT_B5G5R5A1_UNORM_PACK16 :: Format | 
 | 
| pattern FORMAT_A1R5G5B5_UNORM_PACK16 :: Format | 
 | 
| pattern FORMAT_R8_UNORM :: Format | 
 | 
| pattern FORMAT_R8_SNORM :: Format | 
 | 
| pattern FORMAT_R8_USCALED :: Format | 
 | 
| pattern FORMAT_R8_SSCALED :: Format | 
 | 
| pattern FORMAT_R8_UINT :: Format | 
 | 
| pattern FORMAT_R8_SINT :: Format | 
 | 
| pattern FORMAT_R8_SRGB :: Format | 
 | 
| pattern FORMAT_R8G8_UNORM :: Format | 
 | 
| pattern FORMAT_R8G8_SNORM :: Format | 
 | 
| pattern FORMAT_R8G8_USCALED :: Format | 
 | 
| pattern FORMAT_R8G8_SSCALED :: Format | 
 | 
| pattern FORMAT_R8G8_UINT :: Format | 
 | 
| pattern FORMAT_R8G8_SINT :: Format | 
 | 
| pattern FORMAT_R8G8_SRGB :: Format | 
 | 
| pattern FORMAT_R8G8B8_UNORM :: Format | 
 | 
| pattern FORMAT_R8G8B8_SNORM :: Format | 
 | 
| pattern FORMAT_R8G8B8_USCALED :: Format | 
 | 
| pattern FORMAT_R8G8B8_SSCALED :: Format | 
 | 
| pattern FORMAT_R8G8B8_UINT :: Format | 
 | 
| pattern FORMAT_R8G8B8_SINT :: Format | 
 | 
| pattern FORMAT_R8G8B8_SRGB :: Format | 
 | 
| pattern FORMAT_B8G8R8_UNORM :: Format | 
 | 
| pattern FORMAT_B8G8R8_SNORM :: Format | 
 | 
| pattern FORMAT_B8G8R8_USCALED :: Format | 
 | 
| pattern FORMAT_B8G8R8_SSCALED :: Format | 
 | 
| pattern FORMAT_B8G8R8_UINT :: Format | 
 | 
| pattern FORMAT_B8G8R8_SINT :: Format | 
 | 
| pattern FORMAT_B8G8R8_SRGB :: Format | 
 | 
| pattern FORMAT_R8G8B8A8_UNORM :: Format | 
 | 
| pattern FORMAT_R8G8B8A8_SNORM :: Format | 
 | 
| pattern FORMAT_R8G8B8A8_USCALED :: Format | 
 | 
| pattern FORMAT_R8G8B8A8_SSCALED :: Format | 
 | 
| pattern FORMAT_R8G8B8A8_UINT :: Format | 
 | 
| pattern FORMAT_R8G8B8A8_SINT :: Format | 
 | 
| pattern FORMAT_R8G8B8A8_SRGB :: Format | 
 | 
| pattern FORMAT_B8G8R8A8_UNORM :: Format | 
 | 
| pattern FORMAT_B8G8R8A8_SNORM :: Format | 
 | 
| pattern FORMAT_B8G8R8A8_USCALED :: Format | 
 | 
| pattern FORMAT_B8G8R8A8_SSCALED :: Format | 
 | 
| pattern FORMAT_B8G8R8A8_UINT :: Format | 
 | 
| pattern FORMAT_B8G8R8A8_SINT :: Format | 
 | 
| pattern FORMAT_B8G8R8A8_SRGB :: Format | 
 | 
| pattern FORMAT_A8B8G8R8_UNORM_PACK32 :: Format | 
 | 
| pattern FORMAT_A8B8G8R8_SNORM_PACK32 :: Format | 
 | 
| pattern FORMAT_A8B8G8R8_USCALED_PACK32 :: Format | 
 | 
| pattern FORMAT_A8B8G8R8_SSCALED_PACK32 :: Format | 
 | 
| pattern FORMAT_A8B8G8R8_UINT_PACK32 :: Format | 
 | 
| pattern FORMAT_A8B8G8R8_SINT_PACK32 :: Format | 
 | 
| pattern FORMAT_A8B8G8R8_SRGB_PACK32 :: Format | 
 | 
| pattern FORMAT_A2R10G10B10_UNORM_PACK32 :: Format | 
 | 
| pattern FORMAT_A2R10G10B10_SNORM_PACK32 :: Format | 
 | 
| pattern FORMAT_A2R10G10B10_USCALED_PACK32 :: Format | 
 | 
| pattern FORMAT_A2R10G10B10_SSCALED_PACK32 :: Format | 
 | 
| pattern FORMAT_A2R10G10B10_UINT_PACK32 :: Format | 
 | 
| pattern FORMAT_A2R10G10B10_SINT_PACK32 :: Format | 
 | 
| pattern FORMAT_A2B10G10R10_UNORM_PACK32 :: Format | 
 | 
| pattern FORMAT_A2B10G10R10_SNORM_PACK32 :: Format | 
 | 
| pattern FORMAT_A2B10G10R10_USCALED_PACK32 :: Format | 
 | 
| pattern FORMAT_A2B10G10R10_SSCALED_PACK32 :: Format | 
 | 
| pattern FORMAT_A2B10G10R10_UINT_PACK32 :: Format | 
 | 
| pattern FORMAT_A2B10G10R10_SINT_PACK32 :: Format | 
 | 
| pattern FORMAT_R16_UNORM :: Format | 
 | 
| pattern FORMAT_R16_SNORM :: Format | 
 | 
| pattern FORMAT_R16_USCALED :: Format | 
 | 
| pattern FORMAT_R16_SSCALED :: Format | 
 | 
| pattern FORMAT_R16_UINT :: Format | 
 | 
| pattern FORMAT_R16_SINT :: Format | 
 | 
| pattern FORMAT_R16_SFLOAT :: Format | 
 | 
| pattern FORMAT_R16G16_UNORM :: Format | 
 | 
| pattern FORMAT_R16G16_SNORM :: Format | 
 | 
| pattern FORMAT_R16G16_USCALED :: Format | 
 | 
| pattern FORMAT_R16G16_SSCALED :: Format | 
 | 
| pattern FORMAT_R16G16_UINT :: Format | 
 | 
| pattern FORMAT_R16G16_SINT :: Format | 
 | 
| pattern FORMAT_R16G16_SFLOAT :: Format | 
 | 
| pattern FORMAT_R16G16B16_UNORM :: Format | 
 | 
| pattern FORMAT_R16G16B16_SNORM :: Format | 
 | 
| pattern FORMAT_R16G16B16_USCALED :: Format | 
 | 
| pattern FORMAT_R16G16B16_SSCALED :: Format | 
 | 
| pattern FORMAT_R16G16B16_UINT :: Format | 
 | 
| pattern FORMAT_R16G16B16_SINT :: Format | 
 | 
| pattern FORMAT_R16G16B16_SFLOAT :: Format | 
 | 
| pattern FORMAT_R16G16B16A16_UNORM :: Format | 
 | 
| pattern FORMAT_R16G16B16A16_SNORM :: Format | 
 | 
| pattern FORMAT_R16G16B16A16_USCALED :: Format | 
 | 
| pattern FORMAT_R16G16B16A16_SSCALED :: Format | 
 | 
| pattern FORMAT_R16G16B16A16_UINT :: Format | 
 | 
| pattern FORMAT_R16G16B16A16_SINT :: Format | 
 | 
| pattern FORMAT_R16G16B16A16_SFLOAT :: Format | 
 | 
| pattern FORMAT_R32_UINT :: Format | 
 | 
| pattern FORMAT_R32_SINT :: Format | 
 | 
| pattern FORMAT_R32_SFLOAT :: Format | 
 | 
| pattern FORMAT_R32G32_UINT :: Format | 
 | 
| pattern FORMAT_R32G32_SINT :: Format | 
 | 
| pattern FORMAT_R32G32_SFLOAT :: Format | 
 | 
| pattern FORMAT_R32G32B32_UINT :: Format | 
 | 
| pattern FORMAT_R32G32B32_SINT :: Format | 
 | 
| pattern FORMAT_R32G32B32_SFLOAT :: Format | 
 | 
| pattern FORMAT_R32G32B32A32_UINT :: Format | 
 | 
| pattern FORMAT_R32G32B32A32_SINT :: Format | 
 | 
| pattern FORMAT_R32G32B32A32_SFLOAT :: Format | 
 | 
| pattern FORMAT_R64_UINT :: Format | 
 | 
| pattern FORMAT_R64_SINT :: Format | 
 | 
| pattern FORMAT_R64_SFLOAT :: Format | 
 | 
| pattern FORMAT_R64G64_UINT :: Format | 
 | 
| pattern FORMAT_R64G64_SINT :: Format | 
 | 
| pattern FORMAT_R64G64_SFLOAT :: Format | 
 | 
| pattern FORMAT_R64G64B64_UINT :: Format | 
 | 
| pattern FORMAT_R64G64B64_SINT :: Format | 
 | 
| pattern FORMAT_R64G64B64_SFLOAT :: Format | 
 | 
| pattern FORMAT_R64G64B64A64_UINT :: Format | 
 | 
| pattern FORMAT_R64G64B64A64_SINT :: Format | 
 | 
| pattern FORMAT_R64G64B64A64_SFLOAT :: Format | 
 | 
| pattern FORMAT_B10G11R11_UFLOAT_PACK32 :: Format | 
 | 
| pattern FORMAT_E5B9G9R9_UFLOAT_PACK32 :: Format | 
 | 
| pattern FORMAT_D16_UNORM :: Format | 
 | 
| pattern FORMAT_X8_D24_UNORM_PACK32 :: Format | 
 | 
| pattern FORMAT_D32_SFLOAT :: Format | 
 | 
| pattern FORMAT_S8_UINT :: Format | 
 | 
| pattern FORMAT_D16_UNORM_S8_UINT :: Format | 
 | 
| pattern FORMAT_D24_UNORM_S8_UINT :: Format | 
 | 
| pattern FORMAT_D32_SFLOAT_S8_UINT :: Format | 
 | 
| pattern FORMAT_BC1_RGB_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_BC1_RGB_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_BC1_RGBA_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_BC1_RGBA_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_BC2_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_BC2_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_BC3_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_BC3_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_BC4_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_BC4_SNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_BC5_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_BC5_SNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_BC6H_UFLOAT_BLOCK :: Format | 
 | 
| pattern FORMAT_BC6H_SFLOAT_BLOCK :: Format | 
 | 
| pattern FORMAT_BC7_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_BC7_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ETC2_R8G8B8_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ETC2_R8G8B8_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ETC2_R8G8B8A1_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ETC2_R8G8B8A1_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ETC2_R8G8B8A8_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ETC2_R8G8B8A8_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_EAC_R11_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_EAC_R11_SNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_EAC_R11G11_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_EAC_R11G11_SNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_4x4_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_4x4_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_5x4_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_5x4_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_5x5_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_5x5_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_6x5_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_6x5_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_6x6_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_6x6_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_8x5_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_8x5_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_8x6_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_8x6_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_8x8_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_8x8_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_10x5_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_10x5_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_10x6_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_10x6_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_10x8_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_10x8_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_10x10_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_10x10_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_12x10_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_12x10_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_12x12_UNORM_BLOCK :: Format | 
 | 
| pattern FORMAT_ASTC_12x12_SRGB_BLOCK :: Format | 
 | 
| pattern FORMAT_A4B4G4R4_UNORM_PACK16_EXT :: Format | 
 | 
| pattern FORMAT_A4R4G4B4_UNORM_PACK16_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_12x12_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_12x10_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_10x10_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_10x8_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_10x6_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_10x5_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_8x8_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_8x6_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_8x5_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_6x6_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_6x5_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_5x5_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_5x4_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_ASTC_4x4_SFLOAT_BLOCK_EXT :: Format | 
 | 
| pattern FORMAT_PVRTC2_4BPP_SRGB_BLOCK_IMG :: Format | 
 | 
| pattern FORMAT_PVRTC2_2BPP_SRGB_BLOCK_IMG :: Format | 
 | 
| pattern FORMAT_PVRTC1_4BPP_SRGB_BLOCK_IMG :: Format | 
 | 
| pattern FORMAT_PVRTC1_2BPP_SRGB_BLOCK_IMG :: Format | 
 | 
| pattern FORMAT_PVRTC2_4BPP_UNORM_BLOCK_IMG :: Format | 
 | 
| pattern FORMAT_PVRTC2_2BPP_UNORM_BLOCK_IMG :: Format | 
 | 
| pattern FORMAT_PVRTC1_4BPP_UNORM_BLOCK_IMG :: Format | 
 | 
| pattern FORMAT_PVRTC1_2BPP_UNORM_BLOCK_IMG :: Format | 
 | 
| pattern FORMAT_G16_B16_R16_3PLANE_444_UNORM :: Format | 
 | 
| pattern FORMAT_G16_B16R16_2PLANE_422_UNORM :: Format | 
 | 
| pattern FORMAT_G16_B16_R16_3PLANE_422_UNORM :: Format | 
 | 
| pattern FORMAT_G16_B16R16_2PLANE_420_UNORM :: Format | 
 | 
| pattern FORMAT_G16_B16_R16_3PLANE_420_UNORM :: Format | 
 | 
| pattern FORMAT_B16G16R16G16_422_UNORM :: Format | 
 | 
| pattern FORMAT_G16B16G16R16_422_UNORM :: Format | 
 | 
| pattern FORMAT_G12X4_B12X4_R12X4_3PLANE_444_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_G12X4_B12X4R12X4_2PLANE_422_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_G12X4_B12X4_R12X4_3PLANE_422_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_G12X4_B12X4R12X4_2PLANE_420_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_G12X4_B12X4_R12X4_3PLANE_420_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_B12X4G12X4R12X4G12X4_422_UNORM_4PACK16 :: Format | 
 | 
| pattern FORMAT_G12X4B12X4G12X4R12X4_422_UNORM_4PACK16 :: Format | 
 | 
| pattern FORMAT_R12X4G12X4B12X4A12X4_UNORM_4PACK16 :: Format | 
 | 
| pattern FORMAT_R12X4G12X4_UNORM_2PACK16 :: Format | 
 | 
| pattern FORMAT_R12X4_UNORM_PACK16 :: Format | 
 | 
| pattern FORMAT_G10X6_B10X6_R10X6_3PLANE_444_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_G10X6_B10X6R10X6_2PLANE_422_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_G10X6_B10X6_R10X6_3PLANE_422_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_G10X6_B10X6R10X6_2PLANE_420_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_G10X6_B10X6_R10X6_3PLANE_420_UNORM_3PACK16 :: Format | 
 | 
| pattern FORMAT_B10X6G10X6R10X6G10X6_422_UNORM_4PACK16 :: Format | 
 | 
| pattern FORMAT_G10X6B10X6G10X6R10X6_422_UNORM_4PACK16 :: Format | 
 | 
| pattern FORMAT_R10X6G10X6B10X6A10X6_UNORM_4PACK16 :: Format | 
 | 
| pattern FORMAT_R10X6G10X6_UNORM_2PACK16 :: Format | 
 | 
| pattern FORMAT_R10X6_UNORM_PACK16 :: Format | 
 | 
| pattern FORMAT_G8_B8_R8_3PLANE_444_UNORM :: Format | 
 | 
| pattern FORMAT_G8_B8R8_2PLANE_422_UNORM :: Format | 
 | 
| pattern FORMAT_G8_B8_R8_3PLANE_422_UNORM :: Format | 
 | 
| pattern FORMAT_G8_B8R8_2PLANE_420_UNORM :: Format | 
 | 
| pattern FORMAT_G8_B8_R8_3PLANE_420_UNORM :: Format | 
 | 
| pattern FORMAT_B8G8R8G8_422_UNORM :: Format | 
 | 
| pattern FORMAT_G8B8G8R8_422_UNORM :: Format | 
 | 
Instances
| Eq Format Source # | |
| Ord Format Source # | |
| Read Format Source # | |
| Show Format Source # | |
| Storable Format Source # | |
| Zero Format Source # | |
| Defined in Vulkan.Core10.Enums.Format | |
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,
 BlitImageInfo2KHR,
 BufferCopy2KHR,
 BufferCreateInfo,
 BufferDeviceAddressCreateInfoEXT,
 BufferDeviceAddressInfo,
 BufferImageCopy2KHR,
 BufferMemoryBarrier,
 BufferMemoryRequirementsInfo2,
 BufferOpaqueCaptureAddressCreateInfo,
 BufferViewCreateInfo,
 CalibratedTimestampInfoEXT,
 CheckpointDataNV,
 CommandBufferAllocateInfo,
 CommandBufferBeginInfo,
 CommandBufferInheritanceConditionalRenderingInfoEXT,
 CommandBufferInheritanceInfo,
 CommandBufferInheritanceRenderPassTransformInfoQCOM,
 CommandPoolCreateInfo,
 ComputePipelineCreateInfo,
 ConditionalRenderingBeginInfoEXT,
 CooperativeMatrixPropertiesNV,
 CopyAccelerationStructureInfoKHR,
 CopyAccelerationStructureToMemoryInfoKHR,
 CopyBufferInfo2KHR,
 CopyBufferToImageInfo2KHR,
 CopyDescriptorSet,
 CopyImageInfo2KHR,
 CopyImageToBufferInfo2KHR,
 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,
 DeviceDeviceMemoryReportCreateInfoEXT,
 DeviceDiagnosticsConfigCreateInfoNV,
 DeviceEventInfoEXT,
 DeviceGroupBindSparseInfo,
 DeviceGroupCommandBufferBeginInfo,
 DeviceGroupDeviceCreateInfo,
 DeviceGroupPresentCapabilitiesKHR,
 DeviceGroupPresentInfoKHR,
 DeviceGroupRenderPassBeginInfo,
 DeviceGroupSubmitInfo,
 DeviceGroupSwapchainCreateInfoKHR,
 DeviceMemoryOpaqueCaptureAddressInfo,
 DeviceMemoryOverallocationCreateInfoAMD,
 DeviceMemoryReportCallbackDataEXT,
 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,
 ImageBlit2KHR,
 ImageCopy2KHR,
 ImageCreateInfo,
 ImageDrmFormatModifierExplicitCreateInfoEXT,
 ImageDrmFormatModifierListCreateInfoEXT,
 ImageDrmFormatModifierPropertiesEXT,
 ImageFormatListCreateInfo,
 ImageFormatProperties2,
 ImageMemoryBarrier,
 ImageMemoryRequirementsInfo2,
 ImagePipeSurfaceCreateInfoFUCHSIA,
 ImagePlaneMemoryRequirementsInfo,
 ImageResolve2KHR,
 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,
 PhysicalDeviceDeviceMemoryReportFeaturesEXT,
 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,
 PhysicalDevicePortabilitySubsetFeaturesKHR,
 PhysicalDevicePortabilitySubsetPropertiesKHR,
 PhysicalDevicePrivateDataFeaturesEXT,
 PhysicalDeviceProperties2,
 PhysicalDeviceProtectedMemoryFeatures,
 PhysicalDeviceProtectedMemoryProperties,
 PhysicalDevicePushDescriptorPropertiesKHR,
 PhysicalDeviceRayTracingFeaturesKHR,
 PhysicalDeviceRayTracingPropertiesKHR,
 PhysicalDeviceRayTracingPropertiesNV,
 PhysicalDeviceRepresentativeFragmentTestFeaturesNV,
 PhysicalDeviceRobustness2FeaturesEXT,
 PhysicalDeviceRobustness2PropertiesEXT,
 PhysicalDeviceSampleLocationsPropertiesEXT,
 PhysicalDeviceSamplerFilterMinmaxProperties,
 PhysicalDeviceSamplerYcbcrConversionFeatures,
 PhysicalDeviceScalarBlockLayoutFeatures,
 PhysicalDeviceSeparateDepthStencilLayoutsFeatures,
 PhysicalDeviceShaderAtomicFloatFeaturesEXT,
 PhysicalDeviceShaderAtomicInt64Features,
 PhysicalDeviceShaderClockFeaturesKHR,
 PhysicalDeviceShaderCoreProperties2AMD,
 PhysicalDeviceShaderCorePropertiesAMD,
 PhysicalDeviceShaderDemoteToHelperInvocationFeaturesEXT,
 PhysicalDeviceShaderDrawParametersFeatures,
 PhysicalDeviceShaderFloat16Int8Features,
 PhysicalDeviceShaderImageAtomicInt64FeaturesEXT,
 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,
 ResolveImageInfo2KHR,
 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
Instances
newtype QueueFlagBits Source #
VkQueueFlagBits - Bitmask specifying capabilities of queues in a queue family
Description
- QUEUE_GRAPHICS_BITspecifies that queues in this queue family support graphics operations.
- QUEUE_COMPUTE_BITspecifies that queues in this queue family support compute operations.
- QUEUE_TRANSFER_BITspecifies that queues in this queue family support transfer operations.
- QUEUE_SPARSE_BINDING_BITspecifies that queues in this queue family support sparse memory management operations (see Sparse Resources). If any of the sparse resource features are enabled, then at least one queue family must support this bit.
- if QUEUE_PROTECTED_BITis set, then the queues in this queue family support theDEVICE_QUEUE_CREATE_PROTECTED_BITbit. (see Protected Memory). If the physical device supports theprotectedMemoryfeature, at least one of its queue families must support this bit.
If an implementation exposes any queue family that supports graphics operations, at least one queue family of at least one physical device exposed by the implementation must support both graphics and compute operations.
Furthermore, if the protected memory physical device feature is supported, then at least one queue family of at least one physical device exposed by the implementation must support graphics operations, compute operations, and protected memory operations.
Note
All commands that are allowed on a queue that supports transfer
 operations are also allowed on a queue that supports either graphics or
 compute operations. Thus, if the capabilities of a queue family include
 QUEUE_GRAPHICS_BIT or QUEUE_COMPUTE_BIT, then reporting the
 QUEUE_TRANSFER_BIT capability separately for that queue family is
 optional.
For further details see Queues.
See Also
Constructors
| QueueFlagBits Flags | 
Bundled Patterns
| pattern QUEUE_GRAPHICS_BIT :: QueueFlagBits | |
| pattern QUEUE_COMPUTE_BIT :: QueueFlagBits | |
| pattern QUEUE_TRANSFER_BIT :: QueueFlagBits | |
| pattern QUEUE_SPARSE_BINDING_BIT :: QueueFlagBits | |
| pattern QUEUE_PROTECTED_BIT :: QueueFlagBits | 
Instances
type QueueFlags = QueueFlagBits Source #
newtype MemoryPropertyFlagBits Source #
VkMemoryPropertyFlagBits - Bitmask specifying properties for a memory type
Description
For any memory allocated with both the
 MEMORY_PROPERTY_HOST_COHERENT_BIT and the
 MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD, host or device accesses also
 perform automatic memory domain transfer operations, such that writes
 are always automatically available and visible to both host and device
 memory domains.
Note
Device coherence is a useful property for certain debugging use cases (e.g. crash analysis, where performing separate coherence actions could mean values are not reported correctly). However, device coherent accesses may be slower than equivalent accesses without device coherence, particularly if they are also device uncached. For device uncached memory in particular, repeated accesses to the same or neighbouring memory locations over a short time period (e.g. within a frame) may be slower than it would be for the equivalent cached memory type. As such, it is generally inadvisable to use device coherent or device uncached memory except when really needed.
See Also
Constructors
| MemoryPropertyFlagBits Flags | 
Bundled Patterns
| pattern MEMORY_PROPERTY_DEVICE_LOCAL_BIT :: MemoryPropertyFlagBits | 
 | 
| pattern MEMORY_PROPERTY_HOST_VISIBLE_BIT :: MemoryPropertyFlagBits | 
 | 
| pattern MEMORY_PROPERTY_HOST_COHERENT_BIT :: MemoryPropertyFlagBits | 
 | 
| pattern MEMORY_PROPERTY_HOST_CACHED_BIT :: MemoryPropertyFlagBits | 
 | 
| pattern MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT :: MemoryPropertyFlagBits | 
 | 
| pattern MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD :: MemoryPropertyFlagBits | 
 | 
| pattern MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD :: MemoryPropertyFlagBits | 
 | 
| pattern MEMORY_PROPERTY_PROTECTED_BIT :: MemoryPropertyFlagBits | 
 | 
Instances
newtype MemoryHeapFlagBits Source #
Constructors
| MemoryHeapFlagBits Flags | 
Bundled Patterns
| pattern MEMORY_HEAP_DEVICE_LOCAL_BIT :: MemoryHeapFlagBits | 
 | 
| pattern MEMORY_HEAP_MULTI_INSTANCE_BIT :: MemoryHeapFlagBits | 
 | 
Instances
type MemoryHeapFlags = MemoryHeapFlagBits Source #
newtype ImageUsageFlagBits Source #
Constructors
| ImageUsageFlagBits Flags | 
Bundled Patterns
| pattern IMAGE_USAGE_TRANSFER_SRC_BIT :: ImageUsageFlagBits | 
 | 
| pattern IMAGE_USAGE_TRANSFER_DST_BIT :: ImageUsageFlagBits | 
 | 
| pattern IMAGE_USAGE_SAMPLED_BIT :: ImageUsageFlagBits | 
 | 
| pattern IMAGE_USAGE_STORAGE_BIT :: ImageUsageFlagBits | 
 | 
| pattern IMAGE_USAGE_COLOR_ATTACHMENT_BIT :: ImageUsageFlagBits | 
 | 
| pattern IMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT :: ImageUsageFlagBits | 
 | 
| pattern IMAGE_USAGE_TRANSIENT_ATTACHMENT_BIT :: ImageUsageFlagBits | 
 | 
| pattern IMAGE_USAGE_INPUT_ATTACHMENT_BIT :: ImageUsageFlagBits | 
 | 
| pattern IMAGE_USAGE_FRAGMENT_DENSITY_MAP_BIT_EXT :: ImageUsageFlagBits | 
 | 
| pattern IMAGE_USAGE_SHADING_RATE_IMAGE_BIT_NV :: ImageUsageFlagBits | 
 | 
Instances
type ImageUsageFlags = ImageUsageFlagBits Source #
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
Constructors
| ImageCreateFlagBits Flags | 
Bundled Patterns
| pattern IMAGE_CREATE_SPARSE_BINDING_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_SPARSE_RESIDENCY_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_SPARSE_ALIASED_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_MUTABLE_FORMAT_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_CUBE_COMPATIBLE_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_SUBSAMPLED_BIT_EXT :: ImageCreateFlagBits | 
 
 | 
| pattern IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_CORNER_SAMPLED_BIT_NV :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_DISJOINT_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_PROTECTED_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_EXTENDED_USAGE_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_BLOCK_TEXEL_VIEW_COMPATIBLE_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_2D_ARRAY_COMPATIBLE_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT :: ImageCreateFlagBits | 
 | 
| pattern IMAGE_CREATE_ALIAS_BIT :: ImageCreateFlagBits | 
 | 
Instances
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:
- FORMAT_FEATURE_SAMPLED_IMAGE_BITspecifies that an image view can be sampled from.
- FORMAT_FEATURE_STORAGE_IMAGE_BITspecifies that an image view can be used as a storage images.
- FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BITspecifies that an image view can be used as storage image that supports atomic operations.
- FORMAT_FEATURE_COLOR_ATTACHMENT_BITspecifies that an image view can be used as a framebuffer color attachment and as an input attachment.
- FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BITspecifies that an image view can be used as a framebuffer color attachment that supports blending and as an input attachment.
- FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BITspecifies that an image view can be used as a framebuffer depth/stencil attachment and as an input attachment.
- FORMAT_FEATURE_BLIT_SRC_BITspecifies that an image can be used as- srcImagefor the- cmdBlitImage2KHRand- cmdBlitImagecommands.
- FORMAT_FEATURE_BLIT_DST_BITspecifies that an image can be used as- dstImagefor the- cmdBlitImage2KHRand- cmdBlitImagecommands.
- FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BITspecifies that if- FORMAT_FEATURE_SAMPLED_IMAGE_BITis also set, an image view can be used with a sampler that has either of- magFilteror- minFilterset to- FILTER_LINEAR, or- mipmapModeset to- SAMPLER_MIPMAP_MODE_LINEAR. If- FORMAT_FEATURE_BLIT_SRC_BITis also set, an image can be used as the- srcImageto- cmdBlitImage2KHRand- cmdBlitImagewith a- filterof- FILTER_LINEAR. This bit must only be exposed for formats that also support the- FORMAT_FEATURE_SAMPLED_IMAGE_BITor- 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. 
- FORMAT_FEATURE_TRANSFER_SRC_BITspecifies that an image can be used as a source image for copy commands.
- FORMAT_FEATURE_TRANSFER_DST_BITspecifies that an image can be used as a destination image for copy commands and clear commands.
- FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BITspecifies- Imagecan 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.
- FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXTspecifies that- Imagecan be used with a sampler that has either of- magFilteror- minFilterset to- FILTER_CUBIC_EXT, or be the source image for a blit with- filterset to- FILTER_CUBIC_EXT. This bit must only be exposed for formats that also support the- FORMAT_FEATURE_SAMPLED_IMAGE_BIT. If the format being queried is a depth/stencil format, this only specifies that the depth aspect is cubic filterable.
- FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BITspecifies 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- xChromaOffsetand/or- yChromaOffsetof- CHROMA_LOCATION_MIDPOINT. Otherwise both- xChromaOffsetand- yChromaOffsetmust 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.
- FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BITspecifies 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- xChromaOffsetand/or- yChromaOffsetof- CHROMA_LOCATION_COSITED_EVEN. Otherwise both- xChromaOffsetand- yChromaOffsetmust be- CHROMA_LOCATION_MIDPOINT. If neither- FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BITnor- FORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BITis set, the application must not define a sampler Y′CBCR conversion using this format as a source.
- FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_LINEAR_FILTER_BITspecifies that the format can do linear sampler filtering (min/magFilter) whilst sampler Y′CBCR conversion is enabled.
- FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BITspecifies that the format can have different chroma, min, and mag filters.
- FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BITspecifies 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.
- FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BITspecifies that reconstruction can be forcibly made explicit by setting- SamplerYcbcrConversionCreateInfo::- forceExplicitReconstructionto- TRUE. If the format being queried supports- FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BITit must also support- FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT.
- FORMAT_FEATURE_DISJOINT_BITspecifies that a multi-planar image can have the- IMAGE_CREATE_DISJOINT_BITset during image creation. An implementation must not set- FORMAT_FEATURE_DISJOINT_BITfor single-plane formats.
- FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXTspecifies that an image view can be used as a fragment density map attachment.
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:
- FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BITspecifies that the format can be used to create a buffer view that can be bound to a- DESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFERdescriptor.
- FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BITspecifies that the format can be used to create a buffer view that can be bound to a- DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFERdescriptor.
- FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BITspecifies that atomic operations are supported on- DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFERwith this format.
- FORMAT_FEATURE_VERTEX_BUFFER_BITspecifies that the format can be used as a vertex attribute format (- VertexInputAttributeDescription::- format).
See Also
Constructors
| FormatFeatureFlagBits Flags | 
Bundled Patterns
Instances
newtype SampleCountFlagBits Source #
VkSampleCountFlagBits - Bitmask specifying sample counts supported for an image used for storage operations
See Also
AttachmentDescription,
 AttachmentDescription2,
 FramebufferMixedSamplesCombinationNV,
 ImageCreateInfo,
 PhysicalDeviceSparseImageFormatInfo2,
 PipelineMultisampleStateCreateInfo,
 SampleCountFlags,
 SampleLocationsInfoEXT,
 getPhysicalDeviceMultisamplePropertiesEXT,
 getPhysicalDeviceSparseImageFormatProperties
Constructors
| SampleCountFlagBits Flags | 
Bundled Patterns
| pattern SAMPLE_COUNT_1_BIT :: SampleCountFlagBits | 
 | 
| pattern SAMPLE_COUNT_2_BIT :: SampleCountFlagBits | 
 | 
| pattern SAMPLE_COUNT_4_BIT :: SampleCountFlagBits | 
 | 
| pattern SAMPLE_COUNT_8_BIT :: SampleCountFlagBits | 
 | 
| pattern SAMPLE_COUNT_16_BIT :: SampleCountFlagBits | 
 | 
| pattern SAMPLE_COUNT_32_BIT :: SampleCountFlagBits | 
 | 
| pattern SAMPLE_COUNT_64_BIT :: SampleCountFlagBits | 
 | 
Instances
type FN_vkInternalAllocationNotification = ("pUserData" ::: Ptr ()) -> CSize -> InternalAllocationType -> SystemAllocationScope -> IO () Source #
type PFN_vkInternalAllocationNotification = FunPtr FN_vkInternalAllocationNotification Source #
PFN_vkInternalAllocationNotification - Application-defined memory allocation notification function
Description
This is a purely informational callback.
See Also
type FN_vkInternalFreeNotification = ("pUserData" ::: Ptr ()) -> CSize -> InternalAllocationType -> SystemAllocationScope -> IO () Source #
type PFN_vkInternalFreeNotification = FunPtr FN_vkInternalFreeNotification Source #
PFN_vkInternalFreeNotification - Application-defined memory free notification function
See Also
type FN_vkReallocationFunction = ("pUserData" ::: Ptr ()) -> ("pOriginal" ::: Ptr ()) -> CSize -> ("alignment" ::: CSize) -> SystemAllocationScope -> IO (Ptr ()) Source #
type PFN_vkReallocationFunction = FunPtr FN_vkReallocationFunction Source #
PFN_vkReallocationFunction - Application-defined memory reallocation function
Description
pfnReallocation must return an allocation with enough space for
 size bytes, and the contents of the original allocation from bytes
 zero to min(original size, new size) - 1 must be preserved in the
 returned allocation. If size is larger than the old size, the contents
 of the additional space are undefined. If satisfying these requirements
 involves creating a new allocation, then the old allocation should be
 freed.
If pOriginal is NULL, then pfnReallocation must behave
 equivalently to a call to PFN_vkAllocationFunction with the same
 parameter values (without pOriginal).
If size is zero, then pfnReallocation must behave equivalently to
 a call to PFN_vkFreeFunction with the same pUserData parameter
 value, and pMemory equal to pOriginal.
If pOriginal is non-NULL, the implementation must ensure that
 alignment is equal to the alignment used to originally allocate
 pOriginal.
If this function fails and pOriginal is non-NULL the application
 must not free the old allocation.
pfnReallocation must follow the same
 rules for return values as.
See Also
type FN_vkAllocationFunction = ("pUserData" ::: Ptr ()) -> CSize -> ("alignment" ::: CSize) -> SystemAllocationScope -> IO (Ptr ()) Source #
type PFN_vkAllocationFunction = FunPtr FN_vkAllocationFunction Source #
PFN_vkAllocationFunction - Application-defined memory allocation function
Description
If pfnAllocation is unable to allocate the requested memory, it must
 return NULL. If the allocation was successful, it must return a
 valid pointer to memory allocation containing at least size bytes, and
 with the pointer value being a multiple of alignment.
Note
Correct Vulkan operation cannot be assumed if the application does not follow these rules.
For example, pfnAllocation (or pfnReallocation) could cause
 termination of running Vulkan instance(s) on a failed allocation for
 debugging purposes, either directly or indirectly. In these
 circumstances, it cannot be assumed that any part of any affected
 Instance objects are going to operate correctly
 (even destroyInstance), and the
 application must ensure it cleans up properly via other means (e.g.
 process termination).
If pfnAllocation returns NULL, and if the implementation is unable
 to continue correct processing of the current command without the
 requested allocation, it must treat this as a runtime error, and
 generate ERROR_OUT_OF_HOST_MEMORY at the
 appropriate time for the command in which the condition was detected, as
 described in
 Return Codes.
If the implementation is able to continue correct processing of the
 current command without the requested allocation, then it may do so,
 and must not generate
 ERROR_OUT_OF_HOST_MEMORY as a result of
 this failed allocation.
See Also
type PFN_vkFreeFunction = FunPtr FN_vkFreeFunction Source #
PFN_vkFreeFunction - Application-defined memory free function
Description
pMemory may be NULL, which the callback must handle safely. If
 pMemory is non-NULL, it must be a pointer previously allocated by
 pfnAllocation or pfnReallocation. The application should free this
 memory.
See Also
type FN_vkVoidFunction = () -> IO () Source #
type PFN_vkVoidFunction = FunPtr FN_vkVoidFunction Source #
PFN_vkVoidFunction - Placeholder function pointer type returned by queries