Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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 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_A8_UNORM_KHR :: Format
- pattern FORMAT_A1B5G5R5_UNORM_PACK16_KHR :: Format
- pattern FORMAT_R16G16_S10_5_NV :: 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_ASTC_12x12_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_12x10_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_10x10_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_10x8_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_10x6_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_10x5_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_8x8_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_8x6_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_8x5_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_6x6_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_6x5_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_5x5_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_5x4_SFLOAT_BLOCK :: Format
- pattern FORMAT_ASTC_4x4_SFLOAT_BLOCK :: Format
- pattern FORMAT_A4B4G4R4_UNORM_PACK16 :: Format
- pattern FORMAT_A4R4G4B4_UNORM_PACK16 :: Format
- pattern FORMAT_G16_B16R16_2PLANE_444_UNORM :: Format
- pattern FORMAT_G12X4_B12X4R12X4_2PLANE_444_UNORM_3PACK16 :: Format
- pattern FORMAT_G10X6_B10X6R10X6_2PLANE_444_UNORM_3PACK16 :: Format
- pattern FORMAT_G8_B8R8_2PLANE_444_UNORM :: 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 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_OPTICAL_FLOW_BIT_NV :: 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_RDMA_CAPABLE_BIT_NV :: 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_SAMPLE_BLOCK_MATCH_BIT_QCOM :: ImageUsageFlagBits
- pattern IMAGE_USAGE_SAMPLE_WEIGHT_BIT_QCOM :: ImageUsageFlagBits
- pattern IMAGE_USAGE_INVOCATION_MASK_BIT_HUAWEI :: ImageUsageFlagBits
- pattern IMAGE_USAGE_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_HOST_TRANSFER_BIT_EXT :: ImageUsageFlagBits
- pattern IMAGE_USAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR :: ImageUsageFlagBits
- pattern IMAGE_USAGE_FRAGMENT_DENSITY_MAP_BIT_EXT :: 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_FRAGMENT_DENSITY_MAP_OFFSET_BIT_QCOM :: ImageCreateFlagBits
- pattern IMAGE_CREATE_2D_VIEW_COMPATIBLE_BIT_EXT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_MULTISAMPLED_RENDER_TO_SINGLE_SAMPLED_BIT_EXT :: ImageCreateFlagBits
- pattern IMAGE_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT :: 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_SHADING_RATE_ATTACHMENT_BIT_KHR :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT :: FormatFeatureFlagBits
- pattern FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR :: 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
- newtype InstanceCreateFlagBits where
- type InstanceCreateFlags = InstanceCreateFlagBits
- 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
:: 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
::ppEnabledExtensionNames
list must also be present in that list
Valid Usage (Implicit)
-
pCreateInfo
must be a valid pointer to a validInstanceCreateInfo
structure
- If
pAllocator
is notNULL
,pAllocator
must be a valid pointer to a validAllocationCallbacks
structure -
pInstance
must be a valid pointer to aInstance
handle
Return Codes
See Also
VK_VERSION_1_0,
AllocationCallbacks
,
Instance
, InstanceCreateInfo
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 last argument.
To just extract the pair pass (,)
as the last argument.
:: forall io. MonadIO io | |
=> Instance |
|
-> ("allocator" ::: Maybe AllocationCallbacks) |
|
-> io () |
vkDestroyInstance - Destroy an instance of Vulkan
Valid Usage
- If
AllocationCallbacks
were provided wheninstance
was created, a compatible set of callbacks must be provided here - If no
AllocationCallbacks
were provided wheninstance
was created,pAllocator
must beNULL
Valid Usage (Implicit)
- If
instance
is notNULL
,instance
must be a validInstance
handle
- If
pAllocator
is notNULL
,pAllocator
must be a valid pointer to a validAllocationCallbacks
structure
Host Synchronization
- Host access to
instance
must be externally synchronized
- Host access to all
PhysicalDevice
objects enumerated frominstance
must be externally synchronized
See Also
enumeratePhysicalDevices Source #
:: 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, and INCOMPLETE
will be
returned instead of SUCCESS
, to indicate
that not all the available physical devices were returned.
Valid Usage (Implicit)
-
instance
must be a validInstance
handle
-
pPhysicalDeviceCount
must be a valid pointer to auint32_t
value - If the
value referenced by
pPhysicalDeviceCount
is not0
, andpPhysicalDevices
is notNULL
,pPhysicalDevices
must be a valid pointer to an array ofpPhysicalDeviceCount
PhysicalDevice
handles
Return Codes
See Also
:: 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 (“fp” is “function pointer”) for each case. A
valid returned function pointer (“fp”) must not be NULL
.
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 | requested core version2 device-level dispatchable command3 | fp4 |
device | enabled extension device-level dispatchable command3 | fp4 |
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
- Device-level commands which are part of the core version specified
by
ApplicationInfo
::apiVersion
when creating the instance will always return a valid function pointer. If the maintenance5 feature is enabled, core commands beyond that version which are supported by the implementation will returnNULL
, otherwise the implementation may either returnNULL
or a function pointer. If a function pointer is returned, it must not be called. - 3
- In this function, device-level excludes all physical-device-level commands.
- 4
- The returned function pointer must only be called with a
dispatchable object (the first parameter) that is
device
or a child ofdevice
e.g.Device
,Queue
, orCommandBuffer
.
Valid Usage (Implicit)
See Also
:: 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. A
valid returned function pointer (“fp”) must not be NULL
.
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-NULL
instance | *1 | undefined |
NULL | global command2 | fp |
NULL | getInstanceProcAddr | fp5 |
instance | getInstanceProcAddr | fp |
instance | core /dispatchable command/ | fp3 |
instance | enabled instance
extension
dispatchable command
for instance | fp3 |
instance | available device
extension4
dispatchable command
for instance | fp3 |
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 global commands are:
enumerateInstanceVersion
,enumerateInstanceExtensionProperties
,enumerateInstanceLayerProperties
, andcreateInstance
. Dispatchable commands are all other commands which are not global. - 3
- The returned function pointer must only be called with a
dispatchable object (the first parameter) that is
instance
or a child ofinstance
, e.g.Instance
,PhysicalDevice
,Device
,Queue
, orCommandBuffer
. - 4
- An “available device extension” is a device extension supported by
any physical device enumerated by
instance
. - 5
- Starting with Vulkan 1.2,
getInstanceProcAddr
can resolve itself with aNULL
instance pointer.
Valid Usage (Implicit)
- If
instance
is notNULL
,instance
must be a validInstance
handle
See Also
getPhysicalDeviceProperties Source #
:: forall io. MonadIO io | |
=> PhysicalDevice |
|
-> io PhysicalDeviceProperties |
vkGetPhysicalDeviceProperties - Returns properties of a physical device
Valid Usage (Implicit)
See Also
getPhysicalDeviceQueueFamilyProperties Source #
:: 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)
-
physicalDevice
must be a validPhysicalDevice
handle
-
pQueueFamilyPropertyCount
must be a valid pointer to auint32_t
value -
If the value referenced by
pQueueFamilyPropertyCount
is not0
, andpQueueFamilyProperties
is notNULL
,pQueueFamilyProperties
must be a valid pointer to an array ofpQueueFamilyPropertyCount
QueueFamilyProperties
structures
See Also
getPhysicalDeviceMemoryProperties Source #
:: forall io. MonadIO io | |
=> PhysicalDevice |
|
-> io PhysicalDeviceMemoryProperties |
vkGetPhysicalDeviceMemoryProperties - Reports memory information for the specified physical device
Valid Usage (Implicit)
See Also
VK_VERSION_1_0,
PhysicalDevice
, PhysicalDeviceMemoryProperties
getPhysicalDeviceFeatures Source #
:: forall io. MonadIO io | |
=> PhysicalDevice |
|
-> io PhysicalDeviceFeatures |
vkGetPhysicalDeviceFeatures - Reports capabilities of a physical device
Valid Usage (Implicit)
See Also
getPhysicalDeviceFormatProperties Source #
:: forall io. MonadIO io | |
=> PhysicalDevice |
|
-> Format |
|
-> io FormatProperties |
vkGetPhysicalDeviceFormatProperties - Lists physical device’s format capabilities
Valid Usage (Implicit)
See Also
getPhysicalDeviceImageFormatProperties Source #
:: 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
.
If VK_EXT_host_image_copy
is supported, usage
includes
IMAGE_USAGE_SAMPLED_BIT
, and
flags
does not include either of
IMAGE_CREATE_SPARSE_BINDING_BIT
,
IMAGE_CREATE_SPARSE_RESIDENCY_BIT
,
or
IMAGE_CREATE_SPARSE_ALIASED_BIT
,
then the result of calls to getPhysicalDeviceImageFormatProperties
with identical parameters except for the inclusion of
IMAGE_USAGE_HOST_TRANSFER_BIT_EXT
in usage
must be identical.
Return Codes
See Also
VK_VERSION_1_0,
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.
Note
The encoding of driverVersion
is implementation-defined. It may not
use the same encoding as apiVersion
. Applications should follow
information from the vendor on how to extract the version information
from driverVersion
.
On implementations that claim support for the
Roadmap 2022
profile, the major and minor version expressed by apiVersion
must be
at least Vulkan 1.3.
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
VK_VERSION_1_0,
PhysicalDeviceLimits
,
PhysicalDeviceProperties2
,
PhysicalDeviceSparseProperties
,
PhysicalDeviceType
,
getPhysicalDeviceProperties
PhysicalDeviceProperties | |
|
Instances
data ApplicationInfo Source #
VkApplicationInfo - Structure specifying application information
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.
Note
Providing a NULL
InstanceCreateInfo
::pApplicationInfo
or providing
an apiVersion
of 0 is equivalent to providing an apiVersion
of
VK_MAKE_API_VERSION(0,1,0,0)
.
Valid Usage
- If
apiVersion
is not0
, then it must be greater than or equal toAPI_VERSION_1_0
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_APPLICATION_INFO
-
pNext
must beNULL
- If
pApplicationName
is notNULL
,pApplicationName
must be a null-terminated UTF-8 string - If
pEngineName
is notNULL
,pEngineName
must be a null-terminated UTF-8 string
See Also
ApplicationInfo | |
|
Instances
Show ApplicationInfo Source # | |
Defined in Vulkan.Core10.DeviceInitialization showsPrec :: Int -> ApplicationInfo -> ShowS # show :: ApplicationInfo -> String # showList :: [ApplicationInfo] -> ShowS # | |
FromCStruct ApplicationInfo Source # | |
Defined in Vulkan.Core10.DeviceInitialization | |
ToCStruct ApplicationInfo Source # | |
Defined in Vulkan.Core10.DeviceInitialization withCStruct :: ApplicationInfo -> (Ptr ApplicationInfo -> IO b) -> IO b Source # pokeCStruct :: Ptr ApplicationInfo -> ApplicationInfo -> IO b -> IO b Source # withZeroCStruct :: (Ptr ApplicationInfo -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr ApplicationInfo -> IO b -> IO b Source # cStructSize :: Int Source # | |
Zero ApplicationInfo Source # | |
Defined in Vulkan.Core10.DeviceInitialization |
data InstanceCreateInfo (es :: [Type]) Source #
VkInstanceCreateInfo - Structure specifying parameters of a newly created instance
Description
To capture events that occur while creating or destroying an instance,
an application can link a
DebugReportCallbackCreateInfoEXT
structure or a
DebugUtilsMessengerCreateInfoEXT
structure to the pNext
element of the InstanceCreateInfo
structure
given to createInstance
. This callback is only valid for the duration
of the createInstance
and the destroyInstance
call. Use
createDebugReportCallbackEXT
or
createDebugUtilsMessengerEXT
to
create persistent callback objects.
An application can add additional drivers by including the
DirectDriverLoadingListLUNARG
struct to the pNext
element of the InstanceCreateInfo
structure
given to createInstance
.
Note
DirectDriverLoadingListLUNARG
allows applications to ship drivers with themselves. Only drivers that
are designed to work with it should be used, such as drivers that
implement Vulkan in software or that implement Vulkan by translating it
to a different API. Any driver that requires installation should not be
used, such as hardware drivers.
Valid Usage
- If the
pNext
chain ofInstanceCreateInfo
includes aDebugReportCallbackCreateInfoEXT
structure, the list of enabled extensions inppEnabledExtensionNames
must containVK_EXT_debug_report
- If the
pNext
chain ofInstanceCreateInfo
includes aDebugUtilsMessengerCreateInfoEXT
structure, the list of enabled extensions inppEnabledExtensionNames
must containVK_EXT_debug_utils
- If the
pNext
chain includes aExportMetalObjectCreateInfoEXT
structure, itsexportObjectType
member must be eitherEXPORT_METAL_OBJECT_TYPE_METAL_DEVICE_BIT_EXT
orEXPORT_METAL_OBJECT_TYPE_METAL_COMMAND_QUEUE_BIT_EXT
- If
flags
has theINSTANCE_CREATE_ENUMERATE_PORTABILITY_BIT_KHR
bit set, the list of enabled extensions inppEnabledExtensionNames
must containVK_KHR_portability_enumeration
- If the
pNext
chain ofInstanceCreateInfo
includes aDirectDriverLoadingListLUNARG
structure, the list of enabled extensions inppEnabledExtensionNames
must contain VK_LUNARG_direct_driver_loading
Valid Usage (Implicit)
-
sType
must beSTRUCTURE_TYPE_INSTANCE_CREATE_INFO
- Each
pNext
member of any structure (including this one) in thepNext
chain must be eitherNULL
or a pointer to a valid instance ofDebugReportCallbackCreateInfoEXT
,DebugUtilsMessengerCreateInfoEXT
,DirectDriverLoadingListLUNARG
,ExportMetalObjectCreateInfoEXT
,ValidationFeaturesEXT
, orValidationFlagsEXT
- The
sType
value of each struct in thepNext
chain must be unique, with the exception of structures of typeDebugUtilsMessengerCreateInfoEXT
orExportMetalObjectCreateInfoEXT
-
flags
must be a valid combination ofInstanceCreateFlagBits
values - If
pApplicationInfo
is notNULL
,pApplicationInfo
must be a valid pointer to a validApplicationInfo
structure - If
enabledLayerCount
is not0
,ppEnabledLayerNames
must be a valid pointer to an array ofenabledLayerCount
null-terminated UTF-8 strings - If
enabledExtensionCount
is not0
,ppEnabledExtensionNames
must be a valid pointer to an array ofenabledExtensionCount
null-terminated UTF-8 strings
See Also
VK_VERSION_1_0,
ApplicationInfo
,
InstanceCreateFlags
,
StructureType
, createInstance
InstanceCreateInfo | |
|
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) specifies 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
, andz
of aOffset3D
parameter must be integer multiples of Ax, Ay, and Az, respectively.width
of aExtent3D
parameter must be an integer multiple of Ax, or elsex
+width
must equal the width of the image subresource corresponding to the parameter.height
of aExtent3D
parameter must be an integer multiple of Ay, or elsey
+height
must equal the height of the image subresource corresponding to the parameter.depth
of aExtent3D
parameter must be an integer multiple of Az, or elsez
+depth
must 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
VK_VERSION_1_0,
Extent3D
,
QueueFamilyProperties2
,
QueueFlags
,
getPhysicalDeviceQueueFamilyProperties
QueueFamilyProperties | |
|
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
MEMORY_PROPERTY_DEVICE_LOCAL_BIT
|MEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV
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
propertyFlags
member of X is a strict subset of the set of bit flags returned in thepropertyFlags
member of Y; or - the
propertyFlags
members 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
propertyFlags
members of Y includesMEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
orMEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
and 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
VK_VERSION_1_0,
MemoryHeap
, MemoryType
,
PhysicalDeviceMemoryProperties2
,
getPhysicalDeviceMemoryProperties
PhysicalDeviceMemoryProperties | |
|
Instances
data MemoryType Source #
VkMemoryType - Structure specifying memory type
See Also
VK_VERSION_1_0,
MemoryPropertyFlags
,
PhysicalDeviceMemoryProperties
MemoryType | |
|
Instances
data MemoryHeap Source #
VkMemoryHeap - Structure specifying a memory heap
See Also
VK_VERSION_1_0,
DeviceSize
,
MemoryHeapFlags
,
PhysicalDeviceMemoryProperties
MemoryHeap | |
|
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
VK_VERSION_1_0,
FormatFeatureFlags
,
FormatProperties2
,
getPhysicalDeviceFormatProperties
FormatProperties | |
|
Instances
data ImageFormatProperties Source #
VkImageFormatProperties - Structure specifying an image format properties
Members
maxExtent
are the maximum image dimensions. See the Allowed Extent Values section below for how these values are constrained bytype
.
maxMipLevels
is the maximum number of mipmap levels.maxMipLevels
must be equal to the number of levels in the complete mipmap chain based on themaxExtent.width
,maxExtent.height
, andmaxExtent.depth
, except when one of the following conditions is true, in which case it may instead be1
:getPhysicalDeviceImageFormatProperties
::tiling
wasIMAGE_TILING_LINEAR
PhysicalDeviceImageFormatInfo2
::tiling
wasIMAGE_TILING_DRM_FORMAT_MODIFIER_EXT
- the
PhysicalDeviceImageFormatInfo2
::pNext
chain included aPhysicalDeviceExternalImageFormatInfo
structure with a handle type included in thehandleTypes
member for which mipmap image support is not required - image
format
is one of the formats that require a sampler Y′CBCR conversion flags
containsIMAGE_CREATE_SUBSAMPLED_BIT_EXT
maxArrayLayers
is the maximum number of array layers.maxArrayLayers
must be no less thanPhysicalDeviceLimits
::maxImageArrayLayers
, except when one of the following conditions is true, in which case it may instead be1
:tiling
isIMAGE_TILING_LINEAR
tiling
isIMAGE_TILING_OPTIMAL
andtype
isIMAGE_TYPE_3D
format
is one of the formats that require a sampler Y′CBCR conversion
- If
tiling
isIMAGE_TILING_DRM_FORMAT_MODIFIER_EXT
, thenmaxArrayLayers
must not be 0. sampleCounts
is a bitmask ofSampleCountFlagBits
specifying all the supported sample counts for this image as described below.maxResourceSize
is 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.maxResourceSize
must 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
VK_VERSION_1_0,
DeviceSize
,
Extent3D
,
ExternalImageFormatPropertiesNV
,
ImageFormatProperties2
,
SampleCountFlags
,
getPhysicalDeviceImageFormatProperties
Instances
data PhysicalDeviceFeatures Source #
VkPhysicalDeviceFeatures - Structure describing the fine-grained features that can be supported by an implementation
Members
This structure describes the following features:
See Also
VK_VERSION_1_0,
Bool32
,
DeviceCreateInfo
,
PhysicalDeviceFeatures2
,
getPhysicalDeviceFeatures
PhysicalDeviceFeatures | |
|
Instances
data PhysicalDeviceSparseProperties Source #
VkPhysicalDeviceSparseProperties - Structure specifying physical device sparse memory properties
See Also
PhysicalDeviceSparseProperties | |
|
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
.
See Also
VK_VERSION_1_0,
Bool32
,
DeviceSize
, PhysicalDeviceProperties
,
SampleCountFlags
PhysicalDeviceLimits | |
|
Instances
VkInstance - Opaque handle to an instance object
See Also
VK_VERSION_1_0,
createAndroidSurfaceKHR
,
createDebugReportCallbackEXT
,
createDebugUtilsMessengerEXT
,
createDirectFBSurfaceEXT
,
createDisplayPlaneSurfaceKHR
,
createHeadlessSurfaceEXT
,
createIOSSurfaceMVK
,
createImagePipeSurfaceFUCHSIA
,
createInstance
,
createMacOSSurfaceMVK
,
createMetalSurfaceEXT
,
createScreenSurfaceQNX
,
createStreamDescriptorSurfaceGGP
,
createViSurfaceNN
,
createWaylandSurfaceKHR
,
createWin32SurfaceKHR
,
createXcbSurfaceKHR
,
createXlibSurfaceKHR
,
debugReportMessageEXT
,
destroyDebugReportCallbackEXT
,
destroyDebugUtilsMessengerEXT
,
destroyInstance
,
destroySurfaceKHR
,
enumeratePhysicalDeviceGroups
,
enumeratePhysicalDeviceGroupsKHR
,
enumeratePhysicalDevices
,
getInstanceProcAddr
,
submitDebugUtilsMessageEXT
Instances
Show Instance Source # | |
Eq Instance Source # | |
HasObjectType Instance Source # | |
Defined in Vulkan.Core10.Handles objectTypeAndHandle :: Instance -> (ObjectType, Word64) Source # | |
IsHandle Instance Source # | |
Defined in Vulkan.Core10.Handles | |
Zero Instance Source # | |
Defined in Vulkan.Core10.Handles |
data PhysicalDevice Source #
VkPhysicalDevice - Opaque handle to a physical device object
See Also
VK_VERSION_1_0,
DeviceGroupDeviceCreateInfo
,
PhysicalDeviceGroupProperties
,
acquireDrmDisplayEXT
,
acquireWinrtDisplayNV
,
acquireXlibDisplayEXT
,
createDevice
,
createDisplayModeKHR
,
enumerateDeviceExtensionProperties
,
enumerateDeviceLayerProperties
,
enumeratePhysicalDeviceQueueFamilyPerformanceQueryCountersKHR
,
enumeratePhysicalDevices
,
getDisplayModeProperties2KHR
,
getDisplayModePropertiesKHR
,
getDisplayPlaneCapabilities2KHR
,
getDisplayPlaneCapabilitiesKHR
,
getDisplayPlaneSupportedDisplaysKHR
,
getDrmDisplayEXT
,
getPhysicalDeviceCalibrateableTimeDomainsEXT
,
getPhysicalDeviceCooperativeMatrixPropertiesKHR
,
getPhysicalDeviceCooperativeMatrixPropertiesNV
,
getPhysicalDeviceDirectFBPresentationSupportEXT
,
getPhysicalDeviceDisplayPlaneProperties2KHR
,
getPhysicalDeviceDisplayPlanePropertiesKHR
,
getPhysicalDeviceDisplayProperties2KHR
,
getPhysicalDeviceDisplayPropertiesKHR
,
getPhysicalDeviceExternalBufferProperties
,
getPhysicalDeviceExternalBufferPropertiesKHR
,
getPhysicalDeviceExternalFenceProperties
,
getPhysicalDeviceExternalFencePropertiesKHR
,
getPhysicalDeviceExternalImageFormatPropertiesNV
,
getPhysicalDeviceExternalSemaphoreProperties
,
getPhysicalDeviceExternalSemaphorePropertiesKHR
,
getPhysicalDeviceFeatures
,
getPhysicalDeviceFeatures2
,
getPhysicalDeviceFeatures2KHR
,
getPhysicalDeviceFormatProperties
,
getPhysicalDeviceFormatProperties2
,
getPhysicalDeviceFormatProperties2KHR
,
getPhysicalDeviceFragmentShadingRatesKHR
,
getPhysicalDeviceImageFormatProperties
,
getPhysicalDeviceImageFormatProperties2
,
getPhysicalDeviceImageFormatProperties2KHR
,
getPhysicalDeviceMemoryProperties
,
getPhysicalDeviceMemoryProperties2
,
getPhysicalDeviceMemoryProperties2KHR
,
getPhysicalDeviceMultisamplePropertiesEXT
,
getPhysicalDeviceOpticalFlowImageFormatsNV
,
getPhysicalDevicePresentRectanglesKHR
,
getPhysicalDeviceProperties
,
getPhysicalDeviceProperties2
,
getPhysicalDeviceProperties2KHR
,
getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR
,
getPhysicalDeviceQueueFamilyProperties
,
getPhysicalDeviceQueueFamilyProperties2
,
getPhysicalDeviceQueueFamilyProperties2KHR
,
getPhysicalDeviceScreenPresentationSupportQNX
,
getPhysicalDeviceSparseImageFormatProperties
,
getPhysicalDeviceSparseImageFormatProperties2
,
getPhysicalDeviceSparseImageFormatProperties2KHR
,
getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV
,
getPhysicalDeviceSurfaceCapabilities2EXT
,
getPhysicalDeviceSurfaceCapabilities2KHR
,
getPhysicalDeviceSurfaceCapabilitiesKHR
,
getPhysicalDeviceSurfaceFormats2KHR
,
getPhysicalDeviceSurfaceFormatsKHR
,
getPhysicalDeviceSurfacePresentModes2EXT
,
getPhysicalDeviceSurfacePresentModesKHR
,
getPhysicalDeviceSurfaceSupportKHR
,
getPhysicalDeviceToolProperties
,
getPhysicalDeviceToolPropertiesEXT
,
vkGetPhysicalDeviceVideoCapabilitiesKHR,
vkGetPhysicalDeviceVideoEncodeQualityLevelPropertiesKHR,
vkGetPhysicalDeviceVideoFormatPropertiesKHR,
getPhysicalDeviceWaylandPresentationSupportKHR
,
getPhysicalDeviceWin32PresentationSupportKHR
,
getPhysicalDeviceXcbPresentationSupportKHR
,
getPhysicalDeviceXlibPresentationSupportKHR
,
getRandROutputDisplayEXT
,
getWinrtDisplayNV
,
releaseDisplayEXT
Instances
Show PhysicalDevice Source # | |
Defined in Vulkan.Core10.Handles showsPrec :: Int -> PhysicalDevice -> ShowS # show :: PhysicalDevice -> String # showList :: [PhysicalDevice] -> ShowS # | |
Eq PhysicalDevice Source # | |
Defined in Vulkan.Core10.Handles (==) :: PhysicalDevice -> PhysicalDevice -> Bool # (/=) :: PhysicalDevice -> PhysicalDevice -> Bool # | |
HasObjectType PhysicalDevice Source # | |
Defined in Vulkan.Core10.Handles objectTypeAndHandle :: PhysicalDevice -> (ObjectType, Word64) Source # | |
IsHandle PhysicalDevice Source # | |
Defined in Vulkan.Core10.Handles | |
Zero PhysicalDevice Source # | |
Defined in Vulkan.Core10.Handles |
data AllocationCallbacks Source #
VkAllocationCallbacks - Structure containing callback function pointers for memory allocation
Description
pUserData
is a value to be interpreted by the implementation of the callbacks. When any of the callbacks inAllocationCallbacks
are called, the Vulkan implementation will pass this value as the first parameter to the callback. This value can vary each time an allocator is passed into a command, even when the same object takes an allocator in multiple commands.
pfnAllocation
is aPFN_vkAllocationFunction
pointer to an application-defined memory allocation function.pfnReallocation
is aPFN_vkReallocationFunction
pointer to an application-defined memory reallocation function.pfnFree
is aPFN_vkFreeFunction
pointer to an application-defined memory free function.pfnInternalAllocation
is aPFN_vkInternalAllocationNotification
pointer to an application-defined function that is called by the implementation when the implementation makes internal allocations.pfnInternalFree
is aPFN_vkInternalFreeNotification
pointer to an application-defined function that is called by the implementation when the implementation frees internal allocations.
Valid Usage
-
pfnAllocation
must be a valid pointer to a valid user-definedPFN_vkAllocationFunction
-
pfnReallocation
must be a valid pointer to a valid user-definedPFN_vkReallocationFunction
-
pfnFree
must be a valid pointer to a valid user-definedPFN_vkFreeFunction
- If either
of
pfnInternalAllocation
orpfnInternalFree
is notNULL
, both must be valid callbacks
See Also
PFN_vkAllocationFunction
,
PFN_vkFreeFunction
,
PFN_vkInternalAllocationNotification
,
PFN_vkInternalFreeNotification
,
PFN_vkReallocationFunction
,
VK_VERSION_1_0,
allocateMemory
,
createAccelerationStructureKHR
,
createAccelerationStructureNV
,
createAndroidSurfaceKHR
,
createBuffer
,
createBufferCollectionFUCHSIA
,
createBufferView
,
createCommandPool
,
createComputePipelines
,
createCuFunctionNVX
,
createCuModuleNVX
,
createCudaFunctionNV
,
createCudaModuleNV
,
createDebugReportCallbackEXT
,
createDebugUtilsMessengerEXT
,
createDeferredOperationKHR
,
createDescriptorPool
,
createDescriptorSetLayout
,
createDescriptorUpdateTemplate
,
createDescriptorUpdateTemplateKHR
,
createDevice
,
createDirectFBSurfaceEXT
,
createDisplayModeKHR
,
createDisplayPlaneSurfaceKHR
,
createEvent
,
createExecutionGraphPipelinesAMDX
,
createFence
,
createFramebuffer
,
createGraphicsPipelines
,
createHeadlessSurfaceEXT
,
createIOSSurfaceMVK
,
createImage
,
createImagePipeSurfaceFUCHSIA
,
createImageView
,
createIndirectCommandsLayoutNV
,
createInstance
,
createMacOSSurfaceMVK
,
createMetalSurfaceEXT
,
createMicromapEXT
,
createOpticalFlowSessionNV
,
createPipelineCache
,
createPipelineLayout
,
createPrivateDataSlot
,
createPrivateDataSlotEXT
,
createQueryPool
,
createRayTracingPipelinesKHR
,
createRayTracingPipelinesNV
,
createRenderPass
,
createRenderPass2
,
createRenderPass2KHR
,
createSampler
,
createSamplerYcbcrConversion
,
createSamplerYcbcrConversionKHR
,
createScreenSurfaceQNX
,
createSemaphore
,
createShaderModule
,
createShadersEXT
,
createSharedSwapchainsKHR
,
createStreamDescriptorSurfaceGGP
,
createSwapchainKHR
,
createValidationCacheEXT
,
createViSurfaceNN
,
vkCreateVideoSessionKHR,
vkCreateVideoSessionParametersKHR,
createWaylandSurfaceKHR
,
createWin32SurfaceKHR
,
createXcbSurfaceKHR
,
createXlibSurfaceKHR
,
destroyAccelerationStructureKHR
,
destroyAccelerationStructureNV
,
destroyBuffer
,
destroyBufferCollectionFUCHSIA
,
destroyBufferView
,
destroyCommandPool
,
destroyCuFunctionNVX
,
destroyCuModuleNVX
,
destroyCudaFunctionNV
,
destroyCudaModuleNV
,
destroyDebugReportCallbackEXT
,
destroyDebugUtilsMessengerEXT
,
destroyDeferredOperationKHR
,
destroyDescriptorPool
,
destroyDescriptorSetLayout
,
destroyDescriptorUpdateTemplate
,
destroyDescriptorUpdateTemplateKHR
,
destroyDevice
,
destroyEvent
, destroyFence
,
destroyFramebuffer
,
destroyImage
,
destroyImageView
,
destroyIndirectCommandsLayoutNV
,
destroyInstance
,
destroyMicromapEXT
,
destroyOpticalFlowSessionNV
,
destroyPipeline
,
destroyPipelineCache
,
destroyPipelineLayout
,
destroyPrivateDataSlot
,
destroyPrivateDataSlotEXT
,
destroyQueryPool
,
destroyRenderPass
,
destroySampler
,
destroySamplerYcbcrConversion
,
destroySamplerYcbcrConversionKHR
,
destroySemaphore
,
destroyShaderEXT
,
destroyShaderModule
,
destroySurfaceKHR
,
destroySwapchainKHR
,
destroyValidationCacheEXT
,
vkDestroyVideoSessionKHR,
vkDestroyVideoSessionParametersKHR,
freeMemory
,
registerDeviceEventEXT
,
registerDisplayEventEXT
Instances
VkImageType - Specifies the type of an image object
See Also
VK_VERSION_1_0,
ImageCreateInfo
,
PhysicalDeviceImageFormatInfo2
,
PhysicalDeviceSparseImageFormatInfo2
,
VkVideoFormatPropertiesKHR,
getPhysicalDeviceExternalImageFormatPropertiesNV
,
getPhysicalDeviceImageFormatProperties
,
getPhysicalDeviceSparseImageFormatProperties
pattern IMAGE_TYPE_1D :: ImageType |
|
pattern IMAGE_TYPE_2D :: ImageType |
|
pattern IMAGE_TYPE_3D :: ImageType |
|
Instances
Storable ImageType Source # | |
Defined in Vulkan.Core10.Enums.ImageType | |
Read ImageType Source # | |
Show ImageType Source # | |
Eq ImageType Source # | |
Ord 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
VK_VERSION_1_0,
ImageCreateInfo
,
PhysicalDeviceImageFormatInfo2
,
PhysicalDeviceSparseImageFormatInfo2
,
VkVideoFormatPropertiesKHR,
getPhysicalDeviceExternalImageFormatPropertiesNV
,
getPhysicalDeviceImageFormatProperties
,
getPhysicalDeviceSparseImageFormatProperties
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
,
VK_VERSION_1_0
pattern INTERNAL_ALLOCATION_TYPE_EXECUTABLE :: InternalAllocationType |
|
Instances
newtype SystemAllocationScope Source #
VkSystemAllocationScope - Allocation scope
Description
SYSTEM_ALLOCATION_SCOPE_COMMAND
specifies that the allocation is scoped to the duration of the Vulkan command.
SYSTEM_ALLOCATION_SCOPE_OBJECT
specifies that the allocation is scoped to the lifetime of the Vulkan object that is being created or used.SYSTEM_ALLOCATION_SCOPE_CACHE
specifies that the allocation is scoped to the lifetime of aPipelineCache
orValidationCacheEXT
object.SYSTEM_ALLOCATION_SCOPE_DEVICE
specifies that the allocation is scoped to the lifetime of the Vulkan device.SYSTEM_ALLOCATION_SCOPE_INSTANCE
specifies 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_COMMAND
allocation 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 parentDevice
has an allocator it will be used, else if the parentInstance
has an allocator it will be used. Else, - If an allocation is associated with a
ValidationCacheEXT
orPipelineCache
object, the allocator will use theSYSTEM_ALLOCATION_SCOPE_CACHE
allocation 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
Device
orInstance
, 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
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
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
VK_VERSION_1_0,
AccelerationStructureGeometryTrianglesDataKHR
,
AccelerationStructureTrianglesDisplacementMicromapNV
,
AndroidHardwareBufferFormatProperties2ANDROID
,
AndroidHardwareBufferFormatPropertiesANDROID
,
AndroidHardwareBufferFormatResolvePropertiesANDROID
,
AttachmentDescription
,
AttachmentDescription2
,
BufferViewCreateInfo
,
CommandBufferInheritanceRenderingInfo
,
DescriptorAddressInfoEXT
,
FramebufferAttachmentImageInfo
,
GeometryTrianglesNV
,
ImageCreateInfo
,
ImageFormatListCreateInfo
,
ImageViewASTCDecodeModeEXT
,
ImageViewCreateInfo
,
OpticalFlowImageFormatPropertiesNV
,
OpticalFlowSessionCreateInfoNV
,
PhysicalDeviceImageFormatInfo2
,
PhysicalDeviceSparseImageFormatInfo2
,
PipelineRenderingCreateInfo
,
RenderingAreaInfoKHR
,
SamplerCustomBorderColorCreateInfoEXT
,
SamplerYcbcrConversionCreateInfo
,
ScreenBufferFormatPropertiesQNX
,
SurfaceFormatKHR
,
SwapchainCreateInfoKHR
,
VertexInputAttributeDescription
,
VertexInputAttributeDescription2EXT
,
VkVideoFormatPropertiesKHR,
VkVideoSessionCreateInfoKHR,
getPhysicalDeviceExternalImageFormatPropertiesNV
,
getPhysicalDeviceFormatProperties
,
getPhysicalDeviceFormatProperties2
,
getPhysicalDeviceFormatProperties2KHR
,
getPhysicalDeviceImageFormatProperties
,
getPhysicalDeviceSparseImageFormatProperties
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_A8_UNORM_KHR :: Format |
|
pattern FORMAT_A1B5G5R5_UNORM_PACK16_KHR :: Format |
|
pattern FORMAT_R16G16_S10_5_NV :: 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_ASTC_12x12_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_12x10_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_10x10_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_10x8_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_10x6_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_10x5_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_8x8_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_8x6_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_8x5_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_6x6_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_6x5_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_5x5_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_5x4_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_ASTC_4x4_SFLOAT_BLOCK :: Format |
|
pattern FORMAT_A4B4G4R4_UNORM_PACK16 :: Format |
|
pattern FORMAT_A4R4G4B4_UNORM_PACK16 :: Format |
|
pattern FORMAT_G16_B16R16_2PLANE_444_UNORM :: Format |
|
pattern FORMAT_G12X4_B12X4R12X4_2PLANE_444_UNORM_3PACK16 :: Format |
|
pattern FORMAT_G10X6_B10X6R10X6_2PLANE_444_UNORM_3PACK16 :: Format |
|
pattern FORMAT_G8_B8R8_2PLANE_444_UNORM :: 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
Storable Format Source # | |
Read Format Source # | |
Show Format Source # | |
Eq Format Source # | |
Ord Format Source # | |
Zero Format Source # | |
Defined in Vulkan.Core10.Enums.Format |
newtype QueueFlagBits Source #
VkQueueFlagBits - Bitmask specifying capabilities of queues in a queue family
Description
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 protectedMemory 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
pattern QUEUE_GRAPHICS_BIT :: QueueFlagBits |
|
pattern QUEUE_COMPUTE_BIT :: QueueFlagBits |
|
pattern QUEUE_TRANSFER_BIT :: QueueFlagBits |
|
pattern QUEUE_SPARSE_BINDING_BIT :: QueueFlagBits |
|
pattern QUEUE_OPTICAL_FLOW_BIT_NV :: 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
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_RDMA_CAPABLE_BIT_NV :: 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 #
VkMemoryHeapFlagBits - Bitmask specifying attribute flags for a heap
See Also
pattern MEMORY_HEAP_DEVICE_LOCAL_BIT :: MemoryHeapFlagBits |
|
pattern MEMORY_HEAP_SEU_SAFE_BIT :: MemoryHeapFlagBits | |
pattern MEMORY_HEAP_MULTI_INSTANCE_BIT :: MemoryHeapFlagBits |
|
Instances
type MemoryHeapFlags = MemoryHeapFlagBits Source #
newtype ImageUsageFlagBits Source #
VkImageUsageFlagBits - Bitmask specifying intended usage of an image
See Also
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_SAMPLE_BLOCK_MATCH_BIT_QCOM :: ImageUsageFlagBits | |
pattern IMAGE_USAGE_SAMPLE_WEIGHT_BIT_QCOM :: ImageUsageFlagBits | |
pattern IMAGE_USAGE_INVOCATION_MASK_BIT_HUAWEI :: ImageUsageFlagBits | |
pattern IMAGE_USAGE_ATTACHMENT_FEEDBACK_LOOP_BIT_EXT :: ImageUsageFlagBits |
|
pattern IMAGE_USAGE_HOST_TRANSFER_BIT_EXT :: ImageUsageFlagBits |
|
pattern IMAGE_USAGE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR :: ImageUsageFlagBits |
|
pattern IMAGE_USAGE_FRAGMENT_DENSITY_MAP_BIT_EXT :: 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
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_FRAGMENT_DENSITY_MAP_OFFSET_BIT_QCOM :: ImageCreateFlagBits |
|
pattern IMAGE_CREATE_2D_VIEW_COMPATIBLE_BIT_EXT :: ImageCreateFlagBits |
|
pattern IMAGE_CREATE_MULTISAMPLED_RENDER_TO_SINGLE_SAMPLED_BIT_EXT :: ImageCreateFlagBits |
|
pattern IMAGE_CREATE_DESCRIPTOR_BUFFER_CAPTURE_REPLAY_BIT_EXT :: 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
These values all have the same meaning as the equivalently named values
for FormatFeatureFlags2
and
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_BIT
specifies that an image view can be sampled from.FORMAT_FEATURE_STORAGE_IMAGE_BIT
specifies that an image view can be used as a storage image.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT
specifies that an image view can be used as storage image that supports atomic operations.FORMAT_FEATURE_COLOR_ATTACHMENT_BIT
specifies that an image view can be used as a framebuffer color attachment and as an input attachment.FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT
specifies that an image view can be used as a framebuffer color attachment that supports blending.FORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT
specifies that an image view can be used as a framebuffer depth/stencil attachment and as an input attachment.FORMAT_FEATURE_BLIT_SRC_BIT
specifies that an image can be used assrcImage
for thecmdBlitImage2
andcmdBlitImage
commands.FORMAT_FEATURE_BLIT_DST_BIT
specifies that an image can be used asdstImage
for thecmdBlitImage2
andcmdBlitImage
commands.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT
specifies that ifFORMAT_FEATURE_SAMPLED_IMAGE_BIT
is also set, an image view can be used with a sampler that has either ofmagFilter
orminFilter
set toFILTER_LINEAR
, ormipmapMode
set toSAMPLER_MIPMAP_MODE_LINEAR
. IfFORMAT_FEATURE_BLIT_SRC_BIT
is also set, an image can be used as thesrcImage
tocmdBlitImage2
andcmdBlitImage
with afilter
ofFILTER_LINEAR
. This bit must only be exposed for formats that also support theFORMAT_FEATURE_SAMPLED_IMAGE_BIT
orFORMAT_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. Where depth comparison is supported it may be linear filtered whether this bit is present or not, but where this bit is not present the filtered value may be computed 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_BIT
specifies that an image can be used as a source image for copy commands. If the applicationapiVersion
is Vulkan 1.0 andVK_KHR_maintenance1
is not supported,FORMAT_FEATURE_TRANSFER_SRC_BIT
is implied to be set when the format feature flag is not 0.FORMAT_FEATURE_TRANSFER_DST_BIT
specifies that an image can be used as a destination image for copy commands and clear commands. If the applicationapiVersion
is Vulkan 1.0 andVK_KHR_maintenance1
is not supported,FORMAT_FEATURE_TRANSFER_DST_BIT
is implied to be set when the format feature flag is not 0.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_MINMAX_BIT
specifiesImage
can be used as a sampled image with a min or maxSamplerReductionMode
. This bit must only be exposed for formats that also support theFORMAT_FEATURE_SAMPLED_IMAGE_BIT
.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT
specifies thatImage
can be used with a sampler that has either ofmagFilter
orminFilter
set toFILTER_CUBIC_EXT
, or be the source image for a blit withfilter
set toFILTER_CUBIC_EXT
. This bit must only be exposed for formats that also support theFORMAT_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_BIT
specifies that an application can define a sampler Y′CBCR conversion using this format as a source, and that an image of this format can be used with aSamplerYcbcrConversionCreateInfo
xChromaOffset
and/oryChromaOffset
ofCHROMA_LOCATION_MIDPOINT
. Otherwise bothxChromaOffset
andyChromaOffset
must beCHROMA_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 setFORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT
.FORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT
specifies that an application can define a sampler Y′CBCR conversion using this format as a source, and that an image of this format can be used with aSamplerYcbcrConversionCreateInfo
xChromaOffset
and/oryChromaOffset
ofCHROMA_LOCATION_COSITED_EVEN
. Otherwise bothxChromaOffset
andyChromaOffset
must beCHROMA_LOCATION_MIDPOINT
. If neitherFORMAT_FEATURE_COSITED_CHROMA_SAMPLES_BIT
norFORMAT_FEATURE_MIDPOINT_CHROMA_SAMPLES_BIT
is 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_BIT
specifies that an application can define a sampler Y′CBCR conversion using this format as a source withchromaFilter
set toFILTER_LINEAR
.FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_SEPARATE_RECONSTRUCTION_FILTER_BIT
specifies that the format can have different chroma, min, and mag filters.FORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT
specifies that reconstruction is explicit, as described in https://registry.khronos.org/vulkan/specs/1.3-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_BIT
specifies that reconstruction can be forcibly made explicit by settingSamplerYcbcrConversionCreateInfo
::forceExplicitReconstruction
toTRUE
. If the format being queried supportsFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_BIT
it must also supportFORMAT_FEATURE_SAMPLED_IMAGE_YCBCR_CONVERSION_CHROMA_RECONSTRUCTION_EXPLICIT_FORCEABLE_BIT
.FORMAT_FEATURE_DISJOINT_BIT
specifies that a multi-planar image can have theIMAGE_CREATE_DISJOINT_BIT
set during image creation. An implementation must not setFORMAT_FEATURE_DISJOINT_BIT
for single-plane formats.FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT
specifies that an image view can be used as a fragment density map attachment.FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR
specifies that an image view can be used as a fragment shading rate attachment. An implementation must not set this feature for formats with a numeric format other thanUINT
, or set it as a buffer feature.VK_FORMAT_FEATURE_VIDEO_DECODE_OUTPUT_BIT_KHR
specifies that an image view with this format can be used as a decode output picture in video decode operations.VK_FORMAT_FEATURE_VIDEO_DECODE_DPB_BIT_KHR
specifies that an image view with this format can be used as an output reconstructed picture or an input reference picture in video decode operations.VK_FORMAT_FEATURE_VIDEO_ENCODE_INPUT_BIT_KHR
specifies that an image view with this format can be used as an encode input picture in video encode operations.VK_FORMAT_FEATURE_VIDEO_ENCODE_DPB_BIT_KHR
specifies that an image view with this format can be used as an output reconstructed picture or an input reference picture in video encode operations.Note
Specific video profiles may have additional restrictions on the format and other image creation parameters corresponding to image views used by video coding operations that can be enumerated using the vkGetPhysicalDeviceVideoFormatPropertiesKHR command.
The following bits may be set in bufferFeatures
, specifying that the
features are supported by buffers or
buffer views created with the queried
getPhysicalDeviceFormatProperties
::format
:
FORMAT_FEATURE_UNIFORM_TEXEL_BUFFER_BIT
specifies that the format can be used to create a buffer view that can be bound to aDESCRIPTOR_TYPE_UNIFORM_TEXEL_BUFFER
descriptor.FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_BIT
specifies that the format can be used to create a buffer view that can be bound to aDESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER
descriptor.FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT
specifies that atomic operations are supported onDESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER
with this format.FORMAT_FEATURE_VERTEX_BUFFER_BIT
specifies that the format can be used as a vertex attribute format (VertexInputAttributeDescription
::format
).FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR
specifies that the format can be used as the vertex format when creating an acceleration structure (AccelerationStructureGeometryTrianglesDataKHR
::vertexFormat
). This format can also be used as the vertex format in host memory when doing host acceleration structure builds.
Note
FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT
and
FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT
are only intended to be
advertised for single-component formats, since SPIR-V atomic operations
require a scalar type.
See Also
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 |
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. Where depth comparison is supported it may be linear filtered whether this bit is present or not, but where this bit is not present the filtered value may be computed in an implementation-dependent manner which differs from the normal rules of linear filtering. The resulting value must be in the range [0,1] and should be proportional to, or a weighted average of, the number of comparison passes or failures. |
pattern FORMAT_FEATURE_FRAGMENT_SHADING_RATE_ATTACHMENT_BIT_KHR :: FormatFeatureFlagBits |
|
pattern FORMAT_FEATURE_FRAGMENT_DENSITY_MAP_BIT_EXT :: FormatFeatureFlagBits |
|
pattern FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT :: FormatFeatureFlagBits |
|
pattern FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR :: 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 |
|
Instances
newtype SampleCountFlagBits Source #
VkSampleCountFlagBits - Bitmask specifying sample counts supported for an image used for storage operations
See Also
VK_VERSION_1_0,
AttachmentDescription
,
AttachmentDescription2
,
AttachmentSampleCountInfoAMD
,
CommandBufferInheritanceRenderingInfo
,
FramebufferMixedSamplesCombinationNV
,
ImageCreateInfo
,
MultisampledRenderToSingleSampledInfoEXT
,
PhysicalDeviceFragmentShadingRateEnumsPropertiesNV
,
PhysicalDeviceFragmentShadingRatePropertiesKHR
,
PhysicalDeviceSparseImageFormatInfo2
,
PipelineMultisampleStateCreateInfo
,
SampleCountFlags
,
SampleLocationsInfoEXT
,
cmdSetRasterizationSamplesEXT
,
cmdSetSampleMaskEXT
,
getPhysicalDeviceMultisamplePropertiesEXT
,
getPhysicalDeviceSparseImageFormatProperties
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
newtype InstanceCreateFlagBits Source #
VkInstanceCreateFlagBits - Bitmask specifying behavior of the instance
See Also
pattern INSTANCE_CREATE_ENUMERATE_PORTABILITY_BIT_KHR :: InstanceCreateFlagBits |
|
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
Description
described link:https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-host-allocation-scope[here^].
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
If the reallocation was successful, 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
Parameters
This type is returned from command function pointer queries, and must be
Description
cast to an actual command function pointer before use.