vulkan-2.1.0.0: Bindings to the Vulkan graphics API.

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Core11.Promoted_from_VK_KHR_device_group

Synopsis

Documentation

newtype VkPeerMemoryFeatureFlagBits Source #

VkPeerMemoryFeatureFlagBits - Bitmask specifying supported peer memory features

Description

  • VK_PEER_MEMORY_FEATURE_COPY_SRC_BIT specifies that the memory can be accessed as the source of a vkCmdCopyBuffer, vkCmdCopyImage, vkCmdCopyBufferToImage, or vkCmdCopyImageToBuffer command.
  • VK_PEER_MEMORY_FEATURE_COPY_DST_BIT specifies that the memory can be accessed as the destination of a vkCmdCopyBuffer, vkCmdCopyImage, vkCmdCopyBufferToImage, or vkCmdCopyImageToBuffer command.
  • VK_PEER_MEMORY_FEATURE_GENERIC_SRC_BIT specifies that the memory can be read as any memory access type.
  • VK_PEER_MEMORY_FEATURE_GENERIC_DST_BIT specifies that the memory can be written as any memory access type. Shader atomics are considered to be writes.

Note

The peer memory features of a memory heap also apply to any accesses that may be performed during image layout transitions.

VK_PEER_MEMORY_FEATURE_COPY_DST_BIT must be supported for all host local heaps and for at least one device local heap.

If a device does not support a peer memory feature, it is still valid to use a resource that includes both local and peer memory bindings with the corresponding access type as long as only the local bindings are actually accessed. For example, an application doing split-frame rendering would use framebuffer attachments that include both local and peer memory bindings, but would scissor the rendering to only update local memory.

See Also

VkPeerMemoryFeatureFlags

Instances
Eq VkPeerMemoryFeatureFlagBits Source # 
Instance details
Ord VkPeerMemoryFeatureFlagBits Source # 
Instance details
Read VkPeerMemoryFeatureFlagBits Source # 
Instance details
Show VkPeerMemoryFeatureFlagBits Source # 
Instance details
Storable VkPeerMemoryFeatureFlagBits Source # 
Instance details
Bits VkPeerMemoryFeatureFlagBits Source # 
Instance details

Methods

(.&.) :: VkPeerMemoryFeatureFlagBits -> VkPeerMemoryFeatureFlagBits -> VkPeerMemoryFeatureFlagBits #

(.|.) :: VkPeerMemoryFeatureFlagBits -> VkPeerMemoryFeatureFlagBits -> VkPeerMemoryFeatureFlagBits #

xor :: VkPeerMemoryFeatureFlagBits -> VkPeerMemoryFeatureFlagBits -> VkPeerMemoryFeatureFlagBits #

complement :: VkPeerMemoryFeatureFlagBits -> VkPeerMemoryFeatureFlagBits #

shift :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

rotate :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

zeroBits :: VkPeerMemoryFeatureFlagBits #

bit :: Int -> VkPeerMemoryFeatureFlagBits #

setBit :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

clearBit :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

complementBit :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

testBit :: VkPeerMemoryFeatureFlagBits -> Int -> Bool #

bitSizeMaybe :: VkPeerMemoryFeatureFlagBits -> Maybe Int #

bitSize :: VkPeerMemoryFeatureFlagBits -> Int #

isSigned :: VkPeerMemoryFeatureFlagBits -> Bool #

shiftL :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

unsafeShiftL :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

shiftR :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

unsafeShiftR :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

rotateL :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

rotateR :: VkPeerMemoryFeatureFlagBits -> Int -> VkPeerMemoryFeatureFlagBits #

popCount :: VkPeerMemoryFeatureFlagBits -> Int #

FiniteBits VkPeerMemoryFeatureFlagBits Source # 
Instance details

newtype VkMemoryAllocateFlagBits Source #

VkMemoryAllocateFlagBits - Bitmask specifying flags for a device memory allocation

See Also

VkMemoryAllocateFlags

Instances
Eq VkMemoryAllocateFlagBits Source # 
Instance details
Ord VkMemoryAllocateFlagBits Source # 
Instance details
Read VkMemoryAllocateFlagBits Source # 
Instance details
Show VkMemoryAllocateFlagBits Source # 
Instance details
Storable VkMemoryAllocateFlagBits Source # 
Instance details
Bits VkMemoryAllocateFlagBits Source # 
Instance details
FiniteBits VkMemoryAllocateFlagBits Source # 
Instance details

pattern VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT :: VkMemoryAllocateFlagBits Source #

VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT specifies that memory will be allocated for the devices in VkMemoryAllocateFlagsInfo::deviceMask.

pattern VK_DEPENDENCY_DEVICE_GROUP_BIT :: VkDependencyFlagBits Source #

VK_DEPENDENCY_DEVICE_GROUP_BIT specifies that dependencies are non-device-local dependency.

vkGetDeviceGroupPeerMemoryFeatures :: ("device" ::: VkDevice) -> ("heapIndex" ::: Word32) -> ("localDeviceIndex" ::: Word32) -> ("remoteDeviceIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr VkPeerMemoryFeatureFlags) -> IO () Source #

vkGetDeviceGroupPeerMemoryFeatures - Query supported peer memory features of a device

Parameters

  • device is the logical device that owns the memory.
  • heapIndex is the index of the memory heap from which the memory is allocated.
  • localDeviceIndex is the device index of the physical device that performs the memory access.
  • remoteDeviceIndex is the device index of the physical device that the memory is allocated for.
  • pPeerMemoryFeatures is a pointer to a bitmask of VkPeerMemoryFeatureFlagBits indicating which types of memory accesses are supported for the combination of heap, local, and remote devices.

Valid Usage

  • heapIndex must be less than memoryHeapCount
  • localDeviceIndex must be a valid device index
  • remoteDeviceIndex must be a valid device index
  • localDeviceIndex must not equal remoteDeviceIndex

Valid Usage (Implicit)

  • device must be a valid VkDevice handle

See Also

VkDevice, VkPeerMemoryFeatureFlags

vkCmdSetDeviceMask :: ("commandBuffer" ::: VkCommandBuffer) -> ("deviceMask" ::: Word32) -> IO () Source #

vkCmdSetDeviceMask - Modify device mask of a command buffer

Parameters

  • commandBuffer is command buffer whose current device mask is modified.
  • deviceMask is the new value of the current device mask.

Description

deviceMask is used to filter out subsequent commands from executing on all physical devices whose bit indices are not set in the mask.

Valid Usage

  • deviceMask must be a valid device mask value
  • deviceMask must not be zero
  • deviceMask must not include any set bits that were not in the VkDeviceGroupCommandBufferBeginInfo::deviceMask value when the command buffer began recording.
  • If vkCmdSetDeviceMask is called inside a render pass instance, deviceMask must not include any set bits that were not in the VkDeviceGroupRenderPassBeginInfo::deviceMask value when the render pass instance began recording.

Valid Usage (Implicit)

  • commandBuffer must be a valid VkCommandBuffer handle
  • commandBuffer must be in the recording state
  • The VkCommandPool that commandBuffer was allocated from must support graphics, compute, or transfer operations

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the VkCommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Both Graphics Compute Transfer

See Also

VkCommandBuffer

vkCmdDispatchBase :: ("commandBuffer" ::: VkCommandBuffer) -> ("baseGroupX" ::: Word32) -> ("baseGroupY" ::: Word32) -> ("baseGroupZ" ::: Word32) -> ("groupCountX" ::: Word32) -> ("groupCountY" ::: Word32) -> ("groupCountZ" ::: Word32) -> IO () Source #

vkCmdDispatchBase - Dispatch compute work items

Parameters

  • commandBuffer is the command buffer into which the command will be recorded.
  • baseGroupX is the start value for the X component of WorkgroupId.
  • baseGroupY is the start value for the Y component of WorkgroupId.
  • baseGroupZ is the start value for the Z component of WorkgroupId.
  • groupCountX is the number of local workgroups to dispatch in the X dimension.
  • groupCountY is the number of local workgroups to dispatch in the Y dimension.
  • groupCountZ is the number of local workgroups to dispatch in the Z dimension.

Description

When the command is executed, a global workgroup consisting of groupCountX × groupCountY × groupCountZ local workgroups is assembled, with WorkgroupId values ranging from [baseGroup, baseGroup + groupCount) in each component. vkCmdDispatch is equivalent to vkCmdDispatchBase(0,0,0,groupCountX,groupCountY,groupCountZ).

Valid Usage

  • baseGroupX must be less than VkPhysicalDeviceLimits::maxComputeWorkGroupCount[0]
  • baseGroupX must be less than VkPhysicalDeviceLimits::maxComputeWorkGroupCount[1]
  • baseGroupZ must be less than VkPhysicalDeviceLimits::maxComputeWorkGroupCount[2]
  • groupCountX must be less than or equal to VkPhysicalDeviceLimits::maxComputeWorkGroupCount[0] minus baseGroupX
  • groupCountY must be less than or equal to VkPhysicalDeviceLimits::maxComputeWorkGroupCount[1] minus baseGroupY
  • groupCountZ must be less than or equal to VkPhysicalDeviceLimits::maxComputeWorkGroupCount[2] minus baseGroupZ
  • If any of baseGroupX, baseGroupY, or baseGroupZ are not zero, then the bound compute pipeline must have been created with the VK_PIPELINE_CREATE_DISPATCH_BASE flag.

Valid Usage (Implicit)

  • commandBuffer must be a valid VkCommandBuffer handle
  • commandBuffer must be in the recording state
  • The VkCommandPool that commandBuffer was allocated from must support compute operations
  • This command must only be called outside of a render pass instance

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the VkCommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Outside Compute

See Also

VkCommandBuffer

data VkMemoryAllocateFlagsInfo Source #

VkMemoryAllocateFlagsInfo - Structure controlling how many instances of memory will be allocated

Description

If VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT is not set, the number of instances allocated depends on whether VK_MEMORY_HEAP_MULTI_INSTANCE_BIT is set in the memory heap. If VK_MEMORY_HEAP_MULTI_INSTANCE_BIT is set, then memory is allocated for every physical device in the logical device (as if deviceMask has bits set for all device indices). If VK_MEMORY_HEAP_MULTI_INSTANCE_BIT is not set, then a single instance of memory is allocated (as if deviceMask is set to one).

On some implementations, allocations from a multi-instance heap may consume memory on all physical devices even if the deviceMask excludes some devices. If VkPhysicalDeviceGroupProperties::subsetAllocation is VK_TRUE, then memory is only consumed for the devices in the device mask.

Note

In practice, most allocations on a multi-instance heap will be allocated across all physical devices. Unicast allocation support is an optional optimization for a minority of allocations.

Valid Usage

  • If VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT is set, deviceMask must be a valid device mask.
  • If VK_MEMORY_ALLOCATE_DEVICE_MASK_BIT is set, deviceMask must not be zero

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO

See Also

VkMemoryAllocateFlags, VkStructureType

Constructors

VkMemoryAllocateFlagsInfo 

Fields

data VkDeviceGroupRenderPassBeginInfo Source #

VkDeviceGroupRenderPassBeginInfo - Set the initial device mask and render areas for a render pass instance

Description

The deviceMask serves several purposes. It is an upper bound on the set of physical devices that can be used during the render pass instance, and the initial device mask when the render pass instance begins. Render pass attachment load, store, and resolve operations only apply to physical devices included in the device mask. Subpass dependencies only apply to the physical devices in the device mask.

If deviceRenderAreaCount is not zero, then the elements of pDeviceRenderAreas override the value of VkRenderPassBeginInfo::renderArea, and provide a render area specific to each physical device. These render areas serve the same purpose as VkRenderPassBeginInfo::renderArea, including controlling the region of attachments that are cleared by VK_ATTACHMENT_LOAD_OP_CLEAR and that are resolved into resolve attachments.

If this structure is not present, the render pass instance’s device mask is the value of VkDeviceGroupCommandBufferBeginInfo::deviceMask. If this structure is not present or if deviceRenderAreaCount is zero, VkRenderPassBeginInfo::renderArea is used for all physical devices.

Valid Usage

  • deviceMask must be a valid device mask value
  • deviceMask must not be zero
  • deviceMask must be a subset of the command buffer’s initial device mask
  • deviceRenderAreaCount must either be zero or equal to the number of physical devices in the logical device.

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO
  • If deviceRenderAreaCount is not 0, pDeviceRenderAreas must be a valid pointer to an array of deviceRenderAreaCount VkRect2D structures

See Also

VkRect2D, VkStructureType

Constructors

VkDeviceGroupRenderPassBeginInfo 

Fields

data VkDeviceGroupCommandBufferBeginInfo Source #

VkDeviceGroupCommandBufferBeginInfo - Set the initial device mask for a command buffer

Description

The initial device mask also acts as an upper bound on the set of devices that can ever be in the device mask in the command buffer.

If this structure is not present, the initial value of a command buffer’s device mask is set to include all physical devices in the logical device when the command buffer begins recording.

Valid Usage

  • deviceMask must be a valid device mask value
  • deviceMask must not be zero

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO

See Also

VkStructureType

Constructors

VkDeviceGroupCommandBufferBeginInfo 

Fields

data VkDeviceGroupSubmitInfo Source #

VkDeviceGroupSubmitInfo - Structure indicating which physical devices execute semaphore operations and command buffers

Description

If this structure is not present, semaphore operations and command buffers execute on device index zero.

Valid Usage

  • waitSemaphoreCount must equal VkSubmitInfo::waitSemaphoreCount
  • commandBufferCount must equal VkSubmitInfo::commandBufferCount
  • signalSemaphoreCount must equal VkSubmitInfo::signalSemaphoreCount
  • All elements of pWaitSemaphoreDeviceIndices and pSignalSemaphoreDeviceIndices must be valid device indices
  • All elements of pCommandBufferDeviceMasks must be valid device masks

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO
  • If waitSemaphoreCount is not 0, pWaitSemaphoreDeviceIndices must be a valid pointer to an array of waitSemaphoreCount uint32_t values
  • If commandBufferCount is not 0, pCommandBufferDeviceMasks must be a valid pointer to an array of commandBufferCount uint32_t values
  • If signalSemaphoreCount is not 0, pSignalSemaphoreDeviceIndices must be a valid pointer to an array of signalSemaphoreCount uint32_t values

See Also

VkStructureType

Constructors

VkDeviceGroupSubmitInfo 

Fields

data VkDeviceGroupBindSparseInfo Source #

VkDeviceGroupBindSparseInfo - Structure indicating which instances are bound

Description

These device indices apply to all buffer and image memory binds included in the batch that points to this structure. The semaphore waits and signals for the batch are executed only by the physical device specified by the resourceDeviceIndex.

If this structure is not present, resourceDeviceIndex and memoryDeviceIndex are assumed to be zero.

Valid Usage

  • resourceDeviceIndex and memoryDeviceIndex must both be valid device indices.
  • Each memory allocation bound in this batch must have allocated an instance for memoryDeviceIndex.

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO

See Also

VkStructureType

Constructors

VkDeviceGroupBindSparseInfo 

Fields

type VkPeerMemoryFeatureFlags = VkPeerMemoryFeatureFlagBits Source #

VkPeerMemoryFeatureFlags - Bitmask of VkPeerMemoryFeatureFlagBits

Description

VkPeerMemoryFeatureFlags is a bitmask type for setting a mask of zero or more VkPeerMemoryFeatureFlagBits.

See Also

VkPeerMemoryFeatureFlagBits, vkGetDeviceGroupPeerMemoryFeatures, vkGetDeviceGroupPeerMemoryFeaturesKHR

type VkMemoryAllocateFlags = VkMemoryAllocateFlagBits Source #

VkMemoryAllocateFlags - Bitmask of VkMemoryAllocateFlagBits

Description

VkMemoryAllocateFlags is a bitmask type for setting a mask of zero or more VkMemoryAllocateFlagBits.

See Also

VkMemoryAllocateFlagBits, VkMemoryAllocateFlagsInfo