| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Graphics.Vulkan.Core10.DeviceInitialization
Synopsis
- createInstance :: forall a io. (PokeChain a, MonadIO io) => InstanceCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io Instance
- withInstance :: forall a io r. (PokeChain a, MonadIO io) => (io Instance -> (Instance -> io ()) -> r) -> InstanceCreateInfo a -> Maybe AllocationCallbacks -> 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
 
Documentation
createInstance :: forall a io. (PokeChain a, MonadIO io) => InstanceCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io Instance Source #
vkCreateInstance - Create a new Vulkan instance
Parameters
- pCreateInfois a pointer to a- InstanceCreateInfostructure controlling creation of the instance.
- pAllocatorcontrols host memory allocation as described in the Memory Allocation chapter.
- pInstancepoints a- Instancehandle in which the resulting instance is returned.
Description
createInstance verifies that the requested layers exist. If not,
 createInstance will return
 ERROR_LAYER_NOT_PRESENT. Next
 createInstance verifies that the requested extensions are supported
 (e.g. in the implementation or in any enabled instance layer) and if any
 requested extension is not supported, createInstance must return
 ERROR_EXTENSION_NOT_PRESENT. After
 verifying and enabling the instance layers and extensions the
 Instance object is created and returned
 to the application. If a requested extension is only supported by a
 layer, both the layer and the extension need to be specified at
 createInstance time for the creation to succeed.
Valid Usage
- All
     required extensions
     for each extension in the
     InstanceCreateInfo::ppEnabledExtensionNameslist must also be present in that list
Valid Usage (Implicit)
- pCreateInfomust be a valid pointer to a valid- InstanceCreateInfostructure
- If pAllocatoris notNULL,pAllocatormust be a valid pointer to a validAllocationCallbacksstructure
- pInstancemust be a valid pointer to a- Instancehandle
Return Codes
See Also
withInstance :: forall a io r. (PokeChain a, MonadIO io) => (io Instance -> (Instance -> io ()) -> r) -> InstanceCreateInfo a -> Maybe AllocationCallbacks -> r Source #
A convenience wrapper to make a compatible pair of calls to
 createInstance and destroyInstance
To ensure that destroyInstance is always called: pass
 bracket (or the allocate function from your
 favourite resource management library) as the first argument.
 To just extract the pair pass '(,)' as the first argument.
destroyInstance :: forall io. MonadIO io => Instance -> ("allocator" ::: Maybe AllocationCallbacks) -> io () Source #
vkDestroyInstance - Destroy an instance of Vulkan
Parameters
- instanceis the handle of the instance to destroy.
- pAllocatorcontrols host memory allocation as described in the Memory Allocation chapter.
Valid Usage
- All child objects created using instancemust have been destroyed prior to destroyinginstance
- If AllocationCallbackswere provided wheninstancewas created, a compatible set of callbacks must be provided here
- If no
     AllocationCallbackswere provided wheninstancewas created,pAllocatormust beNULL
Valid Usage (Implicit)
- If instanceis notNULL,instancemust be a validInstancehandle
- If pAllocatoris notNULL,pAllocatormust be a valid pointer to a validAllocationCallbacksstructure
Host Synchronization
- Host access to instancemust be externally synchronized
- Host access to all PhysicalDeviceobjects enumerated frominstancemust be externally synchronized
See Also
enumeratePhysicalDevices :: forall io. MonadIO io => Instance -> io (Result, "physicalDevices" ::: Vector PhysicalDevice) Source #
vkEnumeratePhysicalDevices - Enumerates the physical devices accessible to a Vulkan instance
Parameters
- instanceis a handle to a Vulkan instance previously created with- createInstance.
- pPhysicalDeviceCountis a pointer to an integer related to the number of physical devices available or queried, as described below.
- pPhysicalDevicesis either- NULLor a pointer to an array of- PhysicalDevicehandles.
Description
If pPhysicalDevices is NULL, then the number of physical devices
 available is returned in pPhysicalDeviceCount. Otherwise,
 pPhysicalDeviceCount must point to a variable set by the user to the
 number of elements in the pPhysicalDevices array, and on return the
 variable is overwritten with the number of handles actually written to
 pPhysicalDevices. If pPhysicalDeviceCount is less than the number of
 physical devices available, at most pPhysicalDeviceCount structures
 will be written. If pPhysicalDeviceCount is smaller than the number of
 physical devices available,
 INCOMPLETE will be returned
 instead of SUCCESS, to indicate
 that not all the available physical devices were returned.
Valid Usage (Implicit)
- instancemust be a valid- Instancehandle
- pPhysicalDeviceCountmust be a valid pointer to a- uint32_tvalue
- If the value referenced by pPhysicalDeviceCountis not0, andpPhysicalDevicesis notNULL,pPhysicalDevicesmust be a valid pointer to an array ofpPhysicalDeviceCountPhysicalDevicehandles
Return Codes
See Also
getDeviceProcAddr :: forall io. MonadIO io => Device -> ("name" ::: ByteString) -> io PFN_vkVoidFunction Source #
vkGetDeviceProcAddr - Return a function pointer for a command
Parameters
The table below defines the various use cases for getDeviceProcAddr
 and expected return value for each case.
Description
The returned function pointer is of type
 PFN_vkVoidFunction, and must be
 cast to the type of the command being queried before use. The function
 pointer must only be called with a dispatchable object (the first
 parameter) that is device or a child of device.
| device | pName | return value | 
|---|---|---|
| NULL | *1 | undefined | 
| invalid device | *1 | undefined | 
| device | NULL | undefined | 
| device | core device-level Vulkan command | fp2 | 
| device | enabled extension device-level commands | fp2 | 
| any other case, not covered above | NULL | 
getDeviceProcAddr behavior
- 1
- "*" means any representable value for the parameter (including
     valid values, invalid values, and NULL).
- 2
- The returned function pointer must only be called with a
     dispatchable object (the first parameter) that is deviceor a child ofdevicee.g.Device,Queue, orCommandBuffer.
Valid Usage (Implicit)
See Also
getInstanceProcAddr :: forall io. MonadIO io => Instance -> ("name" ::: ByteString) -> io PFN_vkVoidFunction Source #
vkGetInstanceProcAddr - Return a function pointer for a command
Parameters
- instanceis the instance that the function pointer will be compatible with, or- NULLfor commands not dependent on any instance.
- pNameis the name of the command to obtain.
Description
getInstanceProcAddr itself is obtained in a platform- and loader-
 specific manner. Typically, the loader library will export this command
 as a function symbol, so applications can link against the loader
 library, or load it dynamically and look up the symbol using
 platform-specific APIs.
The table below defines the various use cases for getInstanceProcAddr
 and expected return value (“fp” is “function pointer”) for each case.
The returned function pointer is of type
 PFN_vkVoidFunction, and must be
 cast to the type of the command being queried before use.
| instance | pName | return value | 
|---|---|---|
| *1 | NULL | undefined | 
| invalid non- NULLinstance | *1 | undefined | 
| NULL | enumerateInstanceVersion | fp | 
| NULL | enumerateInstanceExtensionProperties | fp | 
| NULL | enumerateInstanceLayerProperties | fp | 
| NULL | createInstance | fp | 
| instance | core Vulkan command | fp2 | 
| instance | enabled instance extension commands for instance | fp2 | 
| instance | available device extension3 commands for instance | fp2 | 
| any other case, not covered above | NULL | 
getInstanceProcAddr behavior
- 1
- "*" means any representable value for the parameter (including
     valid values, invalid values, and NULL).
- 2
- The returned function pointer must only be called with a
     dispatchable object (the first parameter) that is instanceor a child ofinstance, e.g.Instance,PhysicalDevice,Device,Queue, orCommandBuffer.
- 3
- An “available device extension” is a device extension supported by
     any physical device enumerated by instance.
Valid Usage (Implicit)
- If instanceis notNULL,instancemust be a validInstancehandle
- pNamemust be a null-terminated UTF-8 string
See Also
getPhysicalDeviceProperties :: forall io. MonadIO io => PhysicalDevice -> io PhysicalDeviceProperties Source #
vkGetPhysicalDeviceProperties - Returns properties of a physical device
Parameters
- physicalDeviceis the handle to the physical device whose properties will be queried.
- pPropertiesis a pointer to a- PhysicalDevicePropertiesstructure in which properties are returned.
Valid Usage (Implicit)
See Also
getPhysicalDeviceQueueFamilyProperties :: forall io. MonadIO io => PhysicalDevice -> io ("queueFamilyProperties" ::: Vector QueueFamilyProperties) Source #
vkGetPhysicalDeviceQueueFamilyProperties - Reports properties of the queues of the specified physical device
Parameters
- physicalDeviceis the handle to the physical device whose properties will be queried.
- pQueueFamilyPropertyCountis a pointer to an integer related to the number of queue families available or queried, as described below.
- pQueueFamilyPropertiesis either- NULLor a pointer to an array of- QueueFamilyPropertiesstructures.
Description
If pQueueFamilyProperties is NULL, then the number of queue families
 available is returned in pQueueFamilyPropertyCount. Implementations
 must support at least one queue family. Otherwise,
 pQueueFamilyPropertyCount must point to a variable set by the user
 to the number of elements in the pQueueFamilyProperties array, and on
 return the variable is overwritten with the number of structures
 actually written to pQueueFamilyProperties. If
 pQueueFamilyPropertyCount is less than the number of queue families
 available, at most pQueueFamilyPropertyCount structures will be
 written.
Valid Usage (Implicit)
- physicalDevicemust be a valid- PhysicalDevicehandle
- pQueueFamilyPropertyCountmust be a valid pointer to a- uint32_tvalue
- If the value referenced by pQueueFamilyPropertyCountis not0, andpQueueFamilyPropertiesis notNULL,pQueueFamilyPropertiesmust be a valid pointer to an array ofpQueueFamilyPropertyCountQueueFamilyPropertiesstructures
See Also
getPhysicalDeviceMemoryProperties :: forall io. MonadIO io => PhysicalDevice -> io PhysicalDeviceMemoryProperties Source #
vkGetPhysicalDeviceMemoryProperties - Reports memory information for the specified physical device
Parameters
- physicalDeviceis the handle to the device to query.
- pMemoryPropertiesis a pointer to a- PhysicalDeviceMemoryPropertiesstructure in which the properties are returned.
Valid Usage (Implicit)
See Also
getPhysicalDeviceFeatures :: forall io. MonadIO io => PhysicalDevice -> io PhysicalDeviceFeatures Source #
vkGetPhysicalDeviceFeatures - Reports capabilities of a physical device
Parameters
- physicalDeviceis the physical device from which to query the supported features.
- pFeaturesis a pointer to a- PhysicalDeviceFeaturesstructure in which the physical device features are returned. For each feature, a value of- TRUEspecifies that the feature is supported on this physical device, and- FALSEspecifies that the feature is not supported.
Valid Usage (Implicit)
See Also
getPhysicalDeviceFormatProperties :: forall io. MonadIO io => PhysicalDevice -> Format -> io FormatProperties Source #
vkGetPhysicalDeviceFormatProperties - Lists physical device’s format capabilities
Parameters
- physicalDeviceis the physical device from which to query the format properties.
- formatis the format whose properties are queried.
- pFormatPropertiesis a pointer to a- FormatPropertiesstructure in which physical device properties for- formatare returned.
Valid Usage (Implicit)
See Also
getPhysicalDeviceImageFormatProperties :: forall io. MonadIO io => PhysicalDevice -> Format -> ImageType -> ImageTiling -> ImageUsageFlags -> ImageCreateFlags -> io ImageFormatProperties Source #
vkGetPhysicalDeviceImageFormatProperties - Lists physical device’s image format capabilities
Parameters
- physicalDeviceis the physical device from which to query the image capabilities.
- formatis a- Formatvalue specifying the image format, corresponding to- ImageCreateInfo::- format.
- typeis a- ImageTypevalue specifying the image type, corresponding to- ImageCreateInfo::- imageType.
- tilingis a- ImageTilingvalue specifying the image tiling, corresponding to- ImageCreateInfo::- tiling.
- usageis a bitmask of- ImageUsageFlagBitsspecifying the intended usage of the image, corresponding to- ImageCreateInfo::- usage.
- flagsis a bitmask of- ImageCreateFlagBitsspecifying additional parameters of the image, corresponding to- ImageCreateInfo::- flags.
- pImageFormatPropertiesis a pointer to a- ImageFormatPropertiesstructure in which capabilities are returned.
Description
The format, type, tiling, usage, and flags parameters
 correspond to parameters that would be consumed by
 createImage (as members of
 ImageCreateInfo).
If format is not a supported image format, or if the combination of
 format, type, tiling, usage, and flags is not supported for
 images, then getPhysicalDeviceImageFormatProperties returns
 ERROR_FORMAT_NOT_SUPPORTED.
The limitations on an image format that are reported by
 getPhysicalDeviceImageFormatProperties have the following property: if
 usage1 and usage2 of type
 ImageUsageFlags are
 such that the bits set in usage1 are a subset of the bits set in
 usage2, and flags1 and flags2 of type
 ImageCreateFlags are
 such that the bits set in flags1 are a subset of the bits set in
 flags2, then the limitations for usage1 and flags1 must be no
 more strict than the limitations for usage2 and flags2, for all
 values of format, type, and tiling.
Return Codes
See Also
Format,
 ImageCreateFlags,
 ImageFormatProperties,
 ImageTiling,
 ImageType,
 ImageUsageFlags,
 PhysicalDevice
data PhysicalDeviceProperties Source #
VkPhysicalDeviceProperties - Structure specifying physical device properties
Description
Note
The value of apiVersion may be different than the version returned
 by
 enumerateInstanceVersion;
 either higher or lower. In such cases, the application must not use
 functionality that exceeds the version of Vulkan associated with a given
 object. The pApiVersion parameter returned by
 enumerateInstanceVersion
 is the version associated with a
 Instance and its children, except for a
 PhysicalDevice and its children.
 PhysicalDeviceProperties::apiVersion is the version associated with
 a PhysicalDevice and its children.
The vendorID and deviceID fields are provided to allow applications
 to adapt to device characteristics that are not adequately exposed by
 other Vulkan queries.
Note
These may include performance profiles, hardware errata, or other characteristics.
The vendor identified by vendorID is the entity responsible for the
 most salient characteristics of the underlying implementation of the
 PhysicalDevice being queried.
Note
For example, in the case of a discrete GPU implementation, this should be the GPU chipset vendor. In the case of a hardware accelerator integrated into a system-on-chip (SoC), this should be the supplier of the silicon IP used to create the accelerator.
If the vendor has a
 PCI vendor ID, the low
 16 bits of vendorID must contain that PCI vendor ID, and the
 remaining bits must be set to zero. Otherwise, the value returned
 must be a valid Khronos vendor ID, obtained as described in the
 Vulkan Documentation and Extensions: Procedures and Conventions
 document in the section “Registering a Vendor ID with Khronos”. Khronos
 vendor IDs are allocated starting at 0x10000, to distinguish them from
 the PCI vendor ID namespace. Khronos vendor IDs are symbolically defined
 in the VendorId type.
The vendor is also responsible for the value returned in deviceID. If
 the implementation is driven primarily by a
 PCI device with a
 PCI device ID, the low 16 bits of deviceID
 must contain that PCI device ID, and the remaining bits must be set
 to zero. Otherwise, the choice of what values to return may be
 dictated by operating system or platform policies - but should
 uniquely identify both the device version and any major configuration
 options (for example, core count in the case of multicore devices).
Note
The same device ID should be used for all physical implementations of that device version and configuration. For example, all uses of a specific silicon IP GPU version and configuration should use the same device ID, even if those uses occur in different SoCs.
See Also
PhysicalDeviceLimits,
 PhysicalDeviceProperties2,
 PhysicalDeviceSparseProperties,
 PhysicalDeviceType,
 getPhysicalDeviceProperties
Constructors
| PhysicalDeviceProperties | |
| Fields 
 | |
Instances
data ApplicationInfo Source #
VkApplicationInfo - Structure specifying application info
Description
Vulkan 1.0 implementations were required to return
 ERROR_INCOMPATIBLE_DRIVER if
 apiVersion was larger than 1.0. Implementations that support Vulkan
 1.1 or later must not return
 ERROR_INCOMPATIBLE_DRIVER for any
 value of apiVersion.
Note
Because Vulkan 1.0 implementations may fail with
 ERROR_INCOMPATIBLE_DRIVER,
 applications should determine the version of Vulkan available before
 calling createInstance. If the getInstanceProcAddr returns NULL
 for
 enumerateInstanceVersion,
 it is a Vulkan 1.0 implementation. Otherwise, the application can call
 enumerateInstanceVersion
 to determine the version of Vulkan.
As long as the instance supports at least Vulkan 1.1, an application can use different versions of Vulkan with an instance than it does with a device or physical device.
Note
The Khronos validation layers will treat apiVersion as the highest API
 version the application targets, and will validate API usage against the
 minimum of that version and the implementation version (instance or
 device, depending on context). If an application tries to use
 functionality from a greater version than this, a validation error will
 be triggered.
For example, if the instance supports Vulkan 1.1 and three physical
 devices support Vulkan 1.0, Vulkan 1.1, and Vulkan 1.2, respectively,
 and if the application sets apiVersion to 1.2, the application can
 use the following versions of Vulkan:
- Vulkan 1.0 can be used with the instance and with all physical devices.
- Vulkan 1.1 can be used with the instance and with the physical devices that support Vulkan 1.1 and Vulkan 1.2.
- Vulkan 1.2 can be used with the physical device that supports Vulkan 1.2.
If we modify the above example so that the application sets apiVersion
 to 1.1, then the application must not use Vulkan 1.2 functionality on
 the physical device that supports Vulkan 1.2.
Implicit layers must be disabled if they do not support a version at
 least as high as apiVersion. See the
 Vulkan Loader Specification and Architecture Overview
 document for additional information.
Note
Providing a NULL InstanceCreateInfo::pApplicationInfo or providing
 an apiVersion of 0 is equivalent to providing an apiVersion of
 VK_MAKE_VERSION(1,0,0).
Valid Usage (Implicit)
- sTypemust be- STRUCTURE_TYPE_APPLICATION_INFO
- pNextmust be- NULL
- If pApplicationNameis notNULL,pApplicationNamemust be a null-terminated UTF-8 string
- If pEngineNameis notNULL,pEngineNamemust be a null-terminated UTF-8 string
See Also
Constructors
| ApplicationInfo | |
| Fields 
 | |
Instances
| Show ApplicationInfo Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods showsPrec :: Int -> ApplicationInfo -> ShowS # show :: ApplicationInfo -> String # showList :: [ApplicationInfo] -> ShowS # | |
| FromCStruct ApplicationInfo Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods peekCStruct :: Ptr ApplicationInfo -> IO ApplicationInfo Source # | |
| ToCStruct ApplicationInfo Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods 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 Graphics.Vulkan.Core10.DeviceInitialization Methods | |
data InstanceCreateInfo (es :: [Type]) Source #
VkInstanceCreateInfo - Structure specifying parameters of a newly created instance
Valid Usage (Implicit)
- sTypemust be- STRUCTURE_TYPE_INSTANCE_CREATE_INFO
- Each pNextmember of any structure (including this one) in thepNextchain must be eitherNULLor a pointer to a valid instance ofDebugReportCallbackCreateInfoEXT,DebugUtilsMessengerCreateInfoEXT,ValidationFeaturesEXT, orValidationFlagsEXT
- The sTypevalue of each struct in thepNextchain must be unique
- flagsmust be- 0
- If pApplicationInfois notNULL,pApplicationInfomust be a valid pointer to a validApplicationInfostructure
- If enabledLayerCountis not0,ppEnabledLayerNamesmust be a valid pointer to an array ofenabledLayerCountnull-terminated UTF-8 strings
- If enabledExtensionCountis not0,ppEnabledExtensionNamesmust be a valid pointer to an array ofenabledExtensionCountnull-terminated UTF-8 strings
See Also
ApplicationInfo,
 InstanceCreateFlags,
 StructureType,
 createInstance
Constructors
| InstanceCreateInfo | |
| Fields 
 | |
Instances
data QueueFamilyProperties Source #
VkQueueFamilyProperties - Structure providing information about a queue family
Description
The value returned in minImageTransferGranularity has a unit of
 compressed texel blocks for images having a block-compressed format, and
 a unit of texels otherwise.
Possible values of minImageTransferGranularity are:
- (0,0,0) which indicates that only whole mip levels must be transferred using the image transfer operations on the corresponding queues. In this case, the following restrictions apply to all offset and extent parameters of image transfer operations: 
- (Ax, Ay, Az) where Ax, Ay, and Az are all integer powers of two. In this case the following restrictions apply to all image transfer operations: - x,- y, and- zof a- Offset3Dparameter must be integer multiples of Ax, Ay, and Az, respectively.
- widthof a- Extent3Dparameter must be an integer multiple of Ax, or else- x+- widthmust equal the width of the image subresource corresponding to the parameter.
- heightof a- Extent3Dparameter must be an integer multiple of Ay, or else- y+- heightmust equal the height of the image subresource corresponding to the parameter.
- depthof a- Extent3Dparameter must be an integer multiple of Az, or else- z+- depthmust equal the depth of the image subresource corresponding to the parameter.
- If the format of the image corresponding to the parameters is one of the block-compressed formats then for the purposes of the above calculations the granularity must be scaled up by the compressed texel block dimensions.
 
Queues supporting graphics and/or compute operations must report
 (1,1,1) in minImageTransferGranularity, meaning that there are no
 additional restrictions on the granularity of image transfer operations
 for these queues. Other queues supporting image transfer operations are
 only required to support whole mip level transfers, thus
 minImageTransferGranularity for queues belonging to such queue
 families may be (0,0,0).
The Device Memory section describes memory properties queried from the physical device.
For physical device feature queries see the Features chapter.
See Also
Extent3D,
 QueueFamilyProperties2,
 QueueFlags,
 getPhysicalDeviceQueueFamilyProperties
Constructors
| QueueFamilyProperties | |
| Fields 
 | |
Instances
| Show QueueFamilyProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods showsPrec :: Int -> QueueFamilyProperties -> ShowS # show :: QueueFamilyProperties -> String # showList :: [QueueFamilyProperties] -> ShowS # | |
| FromCStruct QueueFamilyProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods peekCStruct :: Ptr QueueFamilyProperties -> IO QueueFamilyProperties Source # | |
| ToCStruct QueueFamilyProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods withCStruct :: QueueFamilyProperties -> (Ptr QueueFamilyProperties -> IO b) -> IO b Source # pokeCStruct :: Ptr QueueFamilyProperties -> QueueFamilyProperties -> IO b -> IO b Source # withZeroCStruct :: (Ptr QueueFamilyProperties -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr QueueFamilyProperties -> IO b -> IO b Source # cStructSize :: Int Source # | |
| Zero QueueFamilyProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods | |
data PhysicalDeviceMemoryProperties Source #
VkPhysicalDeviceMemoryProperties - Structure specifying physical device memory properties
Description
The PhysicalDeviceMemoryProperties structure describes a number of
 memory heaps as well as a number of memory types that can be used
 to access memory allocated in those heaps. Each heap describes a memory
 resource of a particular size, and each memory type describes a set of
 memory properties (e.g. host cached vs uncached) that can be used with
 a given memory heap. Allocations using a particular memory type will
 consume resources from the heap indicated by that memory type’s heap
 index. More than one memory type may share each heap, and the heaps
 and memory types provide a mechanism to advertise an accurate size of
 the physical memory resources while allowing the memory to be used with
 a variety of different properties.
The number of memory heaps is given by memoryHeapCount and is less
 than or equal to MAX_MEMORY_HEAPS.
 Each heap is described by an element of the memoryHeaps array as a
 MemoryHeap structure. The number of memory types available across all
 memory heaps is given by memoryTypeCount and is less than or equal to
 MAX_MEMORY_TYPES. Each memory type
 is described by an element of the memoryTypes array as a MemoryType
 structure.
At least one heap must include
 MEMORY_HEAP_DEVICE_LOCAL_BIT
 in MemoryHeap::flags. If there are multiple heaps that all have
 similar performance characteristics, they may all include
 MEMORY_HEAP_DEVICE_LOCAL_BIT.
 In a unified memory architecture (UMA) system there is often only a
 single memory heap which is considered to be equally “local” to the host
 and to the device, and such an implementation must advertise the heap
 as device-local.
Each memory type returned by getPhysicalDeviceMemoryProperties must
 have its propertyFlags set to one of the following values:
- 0
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT
- MEMORY_PROPERTY_PROTECTED_BIT
- MEMORY_PROPERTY_PROTECTED_BIT|- MEMORY_PROPERTY_DEVICE_LOCAL_BIT
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
- MEMORY_PROPERTY_DEVICE_LOCAL_BIT|- MEMORY_PROPERTY_HOST_VISIBLE_BIT|- MEMORY_PROPERTY_HOST_CACHED_BIT|- MEMORY_PROPERTY_HOST_COHERENT_BIT|- MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD|- MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
There must be at least one memory type with both the
 MEMORY_PROPERTY_HOST_VISIBLE_BIT
 and
 MEMORY_PROPERTY_HOST_COHERENT_BIT
 bits set in its propertyFlags. There must be at least one memory
 type with the
 MEMORY_PROPERTY_DEVICE_LOCAL_BIT
 bit set in its propertyFlags. If the
 deviceCoherentMemory
 feature is enabled, there must be at least one memory type with the
 MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
 bit set in its propertyFlags.
For each pair of elements X and Y returned in memoryTypes,
 X must be placed at a lower index position than Y if:
- the set of bit flags returned in the propertyFlagsmember of X is a strict subset of the set of bit flags returned in thepropertyFlagsmember of Y; or
- the propertyFlagsmembers of X and Y are equal, and X belongs to a memory heap with greater performance (as determined in an implementation-specific manner) ; or
- the propertyFlagsmembers of Y includesMEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMDorMEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMDand X does not
Note
There is no ordering requirement between X and Y elements for
 the case their propertyFlags members are not in a subset relation.
 That potentially allows more than one possible way to order the same set
 of memory types. Notice that the
 list of all allowed memory property flag combinations
 is written in a valid order. But if instead
 MEMORY_PROPERTY_DEVICE_LOCAL_BIT
 was before
 MEMORY_PROPERTY_HOST_VISIBLE_BIT
 |
 MEMORY_PROPERTY_HOST_COHERENT_BIT,
 the list would still be in a valid order.
There may be a performance penalty for using device coherent or uncached device memory types, and using these accidentally is undesirable. In order to avoid this, memory types with these properties always appear at the end of the list; but are subject to the same rules otherwise.
This ordering requirement enables applications to use a simple search loop to select the desired memory type along the lines of:
// Find a memory in `memoryTypeBitsRequirement` that includes all of `requiredProperties`
int32_t findProperties(const VkPhysicalDeviceMemoryProperties* pMemoryProperties,
                       uint32_t memoryTypeBitsRequirement,
                       VkMemoryPropertyFlags requiredProperties) {
    const uint32_t memoryCount = pMemoryProperties->memoryTypeCount;
    for (uint32_t memoryIndex = 0; memoryIndex < memoryCount; ++memoryIndex) {
        const uint32_t memoryTypeBits = (1 << memoryIndex);
        const bool isRequiredMemoryType = memoryTypeBitsRequirement & memoryTypeBits;
        const VkMemoryPropertyFlags properties =
            pMemoryProperties->memoryTypes[memoryIndex].propertyFlags;
        const bool hasRequiredProperties =
            (properties & requiredProperties) == requiredProperties;
        if (isRequiredMemoryType && hasRequiredProperties)
            return static_cast<int32_t>(memoryIndex);
    }
    // failed to find memory type
    return -1;
}
// Try to find an optimal memory type, or if it does not exist try fallback memory type
// `device` is the VkDevice
// `image` is the VkImage that requires memory to be bound
// `memoryProperties` properties as returned by vkGetPhysicalDeviceMemoryProperties
// `requiredProperties` are the property flags that must be present
// `optimalProperties` are the property flags that are preferred by the application
VkMemoryRequirements memoryRequirements;
vkGetImageMemoryRequirements(device, image, &memoryRequirements);
int32_t memoryType =
    findProperties(&memoryProperties, memoryRequirements.memoryTypeBits, optimalProperties);
if (memoryType == -1) // not found; try fallback properties
    memoryType =
        findProperties(&memoryProperties, memoryRequirements.memoryTypeBits, requiredProperties);See Also
MemoryHeap, MemoryType,
 PhysicalDeviceMemoryProperties2,
 getPhysicalDeviceMemoryProperties
Constructors
| PhysicalDeviceMemoryProperties | |
| Fields 
 | |
Instances
| Show PhysicalDeviceMemoryProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods showsPrec :: Int -> PhysicalDeviceMemoryProperties -> ShowS # show :: PhysicalDeviceMemoryProperties -> String # showList :: [PhysicalDeviceMemoryProperties] -> ShowS # | |
| FromCStruct PhysicalDeviceMemoryProperties Source # | |
| ToCStruct PhysicalDeviceMemoryProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods withCStruct :: PhysicalDeviceMemoryProperties -> (Ptr PhysicalDeviceMemoryProperties -> IO b) -> IO b Source # pokeCStruct :: Ptr PhysicalDeviceMemoryProperties -> PhysicalDeviceMemoryProperties -> IO b -> IO b Source # withZeroCStruct :: (Ptr PhysicalDeviceMemoryProperties -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr PhysicalDeviceMemoryProperties -> IO b -> IO b Source # cStructSize :: Int Source # | |
| Zero PhysicalDeviceMemoryProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods | |
data MemoryType Source #
VkMemoryType - Structure specifying memory type
See Also
Constructors
| MemoryType | |
| Fields 
 | |
Instances
data MemoryHeap Source #
VkMemoryHeap - Structure specifying a memory heap
See Also
Constructors
| MemoryHeap | |
| Fields 
 | |
Instances
data FormatProperties Source #
VkFormatProperties - Structure specifying image format properties
Description
Note
If no format feature flags are supported, the format itself is not supported, and images of that format cannot be created.
If format is a block-compressed format, then bufferFeatures must
 not support any features for the format.
If format is not a multi-plane format then linearTilingFeatures and
 optimalTilingFeatures must not contain
 FORMAT_FEATURE_DISJOINT_BIT.
See Also
FormatFeatureFlags,
 FormatProperties2,
 getPhysicalDeviceFormatProperties
Constructors
| FormatProperties | |
| Fields 
 | |
Instances
data ImageFormatProperties Source #
VkImageFormatProperties - Structure specifying an image format properties
Members
- maxExtentare the maximum image dimensions. See the Allowed Extent Values section below for how these values are constrained by- type.
- maxMipLevelsis the maximum number of mipmap levels.- maxMipLevelsmust be equal to the number of levels in the complete mipmap chain based on the- maxExtent.width,- maxExtent.height, and- maxExtent.depth, except when one of the following conditions is true, in which case it may instead be- 1:- getPhysicalDeviceImageFormatProperties::- tilingwas- IMAGE_TILING_LINEAR
- PhysicalDeviceImageFormatInfo2::- tilingwas- IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT
- the
    PhysicalDeviceImageFormatInfo2::pNextchain included aPhysicalDeviceExternalImageFormatInfostructure with a handle type included in thehandleTypesmember for which mipmap image support is not required
- image formatis one of those listed in https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion
- flagscontains- IMAGE_CREATE_SUBSAMPLED_BIT_EXT
 
- maxArrayLayersis the maximum number of array layers.- maxArrayLayersmust be no less than- PhysicalDeviceLimits::- maxImageArrayLayers, except when one of the following conditions is true, in which case it may instead be- 1:- tilingis- IMAGE_TILING_LINEAR
- tilingis- IMAGE_TILING_OPTIMALand- typeis- IMAGE_TYPE_3D
- formatis one of those listed in https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion
 
- If tilingisIMAGE_TILING_DRM_FORMAT_MODIFIER_EXT, thenmaxArrayLayersmust not be 0.
- sampleCountsis a bitmask of- SampleCountFlagBitsspecifying all the supported sample counts for this image as described below.
- maxResourceSizeis an upper bound on the total image size in bytes, inclusive of all image subresources. Implementations may have an address space limit on total size of a resource, which is advertised by this property.- maxResourceSizemust be at least 231.
Description
Note
There is no mechanism to query the size of an image before creating it,
 to compare that size against maxResourceSize. If an application
 attempts to create an image that exceeds this limit, the creation will
 fail and createImage will return
 ERROR_OUT_OF_DEVICE_MEMORY. While
 the advertised limit must be at least 231, it may not be possible to
 create an image that approaches that size, particularly for
 IMAGE_TYPE_1D.
If the combination of parameters to
 getPhysicalDeviceImageFormatProperties is not supported by the
 implementation for use in createImage,
 then all members of ImageFormatProperties will be filled with zero.
Note
Filling ImageFormatProperties with zero for unsupported formats is an
 exception to the usual rule that output structures have undefined
 contents on error. This exception was unintentional, but is preserved
 for backwards compatibility.
See Also
DeviceSize,
 Extent3D,
 ExternalImageFormatPropertiesNV,
 ImageFormatProperties2,
 SampleCountFlags,
 getPhysicalDeviceImageFormatProperties
Constructors
| ImageFormatProperties | |
| Fields | |
Instances
| Show ImageFormatProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods showsPrec :: Int -> ImageFormatProperties -> ShowS # show :: ImageFormatProperties -> String # showList :: [ImageFormatProperties] -> ShowS # | |
| FromCStruct ImageFormatProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods peekCStruct :: Ptr ImageFormatProperties -> IO ImageFormatProperties Source # | |
| ToCStruct ImageFormatProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods withCStruct :: ImageFormatProperties -> (Ptr ImageFormatProperties -> IO b) -> IO b Source # pokeCStruct :: Ptr ImageFormatProperties -> ImageFormatProperties -> IO b -> IO b Source # withZeroCStruct :: (Ptr ImageFormatProperties -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr ImageFormatProperties -> IO b -> IO b Source # cStructSize :: Int Source # | |
| Zero ImageFormatProperties Source # | |
| Defined in Graphics.Vulkan.Core10.DeviceInitialization Methods | |
data PhysicalDeviceFeatures Source #
VkPhysicalDeviceFeatures - Structure describing the fine-grained features that can be supported by an implementation
Members
The members of the PhysicalDeviceFeatures structure describe the
 following features:
See Also
Bool32,
 DeviceCreateInfo,
 PhysicalDeviceFeatures2,
 getPhysicalDeviceFeatures
Constructors
| PhysicalDeviceFeatures | |
| Fields 
 | |
Instances
data PhysicalDeviceSparseProperties Source #
VkPhysicalDeviceSparseProperties - Structure specifying physical device sparse memory properties
See Also
Constructors
| PhysicalDeviceSparseProperties | |
| Fields 
 | |
Instances
data PhysicalDeviceLimits Source #
VkPhysicalDeviceLimits - Structure reporting implementation-dependent physical device limits
Members
The PhysicalDeviceLimits are properties of the physical device. These
 are available in the limits member of the PhysicalDeviceProperties
 structure which is returned from getPhysicalDeviceProperties.
Description
- 1
- For all bitmasks of
     SampleCountFlagBits, the sample count limits defined above represent the minimum supported sample counts for each image type. Individual images may support additional sample counts, which are queried usinggetPhysicalDeviceImageFormatPropertiesas described in Supported Sample Counts.
See Also
Bool32,
 DeviceSize,
 PhysicalDeviceProperties,
 SampleCountFlags
Constructors
| PhysicalDeviceLimits | |
| Fields 
 | |