vulkan-3.24: Bindings to the Vulkan graphics API.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Vulkan.Extensions.VK_EXT_opacity_micromap

Description

Name

VK_EXT_opacity_micromap - device extension

VK_EXT_opacity_micromap

Name String
VK_EXT_opacity_micromap
Extension Type
Device extension
Registered Extension Number
397
Revision
2
Extension and Version Dependencies
  • Requires support for Vulkan 1.0
  • Requires VK_KHR_acceleration_structure to be enabled for any device-level functionality
  • Requires VK_KHR_synchronization2 to be enabled for any device-level functionality
Contact

Other Extension Metadata

Last Modified Date
2022-08-24
Interactions and External Dependencies
Contributors
  • Christoph Kubisch, NVIDIA
  • Eric Werness, NVIDIA
  • Josh Barczak, Intel
  • Stu Smith, AMD

Description

When adding adding transparency to a ray traced scene, an application can choose between further tessellating the geometry or using an any hit shader to allow the ray through specific parts of the geometry. These options have the downside of either significantly increasing memory consumption or adding runtime overhead to run shader code in the middle of traversal, respectively.

This extension adds the ability to add an opacity micromap to geometry when building an acceleration structure. The opacity micromap compactly encodes opacity information which can be read by the implementation to mark parts of triangles as opaque or transparent. The format is externally visible to allow the application to compress its internal geometry and surface representations into the compressed format ahead of time. The compressed format subdivides each triangle into a set of subtriangles, each of which can be assigned either two or four opacity values. These opacity values can control if a ray hitting that subtriangle is treated as an opaque hit, complete miss, or possible hit, depending on the controls described in Ray Opacity Micromap.

This extension provides:

  • a MicromapEXT structure to store the micromap,
  • functions similar to acceleration structure build functions to build the opacity micromap array, and
  • a structure to extend AccelerationStructureGeometryTrianglesDataKHR to attach a micromap to the geometry of the acceleration structure.

New Object Types

New Commands

New Structures

New Enums

New Bitmasks

New Enum Constants

Reference code

uint32_t BarycentricsToSpaceFillingCurveIndex(float u, float v, uint32_t level)
{
    u = clamp(u, 0.0f, 1.0f);
    v = clamp(v, 0.0f, 1.0f);

    uint32_t iu, iv, iw;

    // Quantize barycentric coordinates
    float fu = u * (1u << level);
    float fv = v * (1u << level);

    iu = (uint32_t)fu;
    iv = (uint32_t)fv;

    float uf = fu - float(iu);
    float vf = fv - float(iv);

    if (iu >= (1u << level)) iu = (1u << level) - 1u;
    if (iv >= (1u << level)) iv = (1u << level) - 1u;

    uint32_t iuv = iu + iv;

    if (iuv >= (1u << level))
        iu -= iuv - (1u << level) + 1u;

    iw = ~(iu + iv);

    if (uf + vf >= 1.0f && iuv < (1u link:https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html# level) - 1u) --iw;

    uint32_t b0 = ~(iu ^ iw);
    b0 &= ((1u << level) - 1u);
    uint32_t t = (iu ^ iv) & b0;

    uint32_t f = t;
    f ^= f [^] 1u;
    f ^= f >> 2u;
    f ^= f >> 4u;
    f ^= f >> 8u;
    uint32_t b1 = ((f ^ iu) & ~b0) | t;

    // Interleave bits
    b0 = (b0 | (b0 << 8u)) & 0x00ff00ffu;
    b0 = (b0 | (b0 << 4u)) & 0x0f0f0f0fu;
    b0 = (b0 | (b0 << 2u)) & 0x33333333u;
    b0 = (b0 | (b0 << 1u)) & 0x55555555u;
    b1 = (b1 | (b1 << 8u)) & 0x00ff00ffu;
    b1 = (b1 | (b1 << 4u)) & 0x0f0f0f0fu;
    b1 = (b1 | (b1 << 2u)) & 0x33333333u;
    b1 = (b1 | (b1 << 1u)) & 0x55555555u;

    return b0 | (b1 << 1u);
}

Issues

  1. Is the build actually similar to an acceleration structure build?
  • Resolved: The build should be much lighter-weight than an acceleration structure build, but the infrastructure is similar enough that it makes sense to keep the concepts compatible.
  1. Why does VkMicromapUsageEXT not have type/pNext?
  • Resolved: There can be a very large number of these structures, so doubling the size of these can be significant memory consumption. Also, an application may be loading these directly from a file which is more compatible with it being a flat structure. The including structures are extensible and are probably a more suitable place to add extensibility.
  1. Why is there a SPIR-V extension?
  • Resolved: There is a ray flag. To be consistent with how the existing ray tracing extensions work that ray flag needs its own extension.
  1. Should there be indirect micromap build?
  • Resolved: Not for now. There is more in-depth usage metadata required and it seems less likely that something like a GPU culling system would need to change the counts for a micromap.
  1. Should micromaps have a micromap device address?
  • Resolved: There is no need right now (can just use the handle) but that is a bit different from acceleration structures, though the two are not completely parallel in their usage.
  1. Why are the alignment requirements defined as a mix of hardcoded values and caps?
  • Resolved: This is most parallel with the definition of VK_KHR_acceleration_structure and maintaining commonality makes it easier for applications to share memory.

Version History

  • Revision 2, 2022-06-22 (Eric Werness)

    • EXTify and clean up for discussion
  • Revision 1, 2022-01-01 (Eric Werness)

    • Initial revision

See Also

AccelerationStructureTrianglesOpacityMicromapEXT, BuildMicromapFlagBitsEXT, BuildMicromapFlagsEXT, BuildMicromapModeEXT, CopyMemoryToMicromapInfoEXT, CopyMicromapInfoEXT, CopyMicromapModeEXT, CopyMicromapToMemoryInfoEXT, MicromapBuildInfoEXT, MicromapBuildSizesInfoEXT, MicromapCreateFlagBitsEXT, MicromapCreateFlagsEXT, MicromapCreateInfoEXT, MicromapEXT, MicromapTriangleEXT, MicromapTypeEXT, MicromapUsageEXT, MicromapVersionInfoEXT, OpacityMicromapFormatEXT, OpacityMicromapSpecialIndexEXT, PhysicalDeviceOpacityMicromapFeaturesEXT, PhysicalDeviceOpacityMicromapPropertiesEXT, buildMicromapsEXT, cmdBuildMicromapsEXT, cmdCopyMemoryToMicromapEXT, cmdCopyMicromapEXT, cmdCopyMicromapToMemoryEXT, cmdWriteMicromapsPropertiesEXT, copyMemoryToMicromapEXT, copyMicromapEXT, copyMicromapToMemoryEXT, createMicromapEXT, destroyMicromapEXT, getDeviceMicromapCompatibilityEXT, getMicromapBuildSizesEXT, writeMicromapsPropertiesEXT

Document Notes

For more information, see the Vulkan Specification

This page is a generated document. Fixes and changes should be made to the generator scripts, not directly.

Synopsis

Documentation

createMicromapEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that creates the acceleration structure object.

-> MicromapCreateInfoEXT

pCreateInfo is a pointer to a MicromapCreateInfoEXT structure containing parameters affecting creation of the micromap.

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

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

-> io MicromapEXT 

vkCreateMicromapEXT - Create a new micromap object

Description

Similar to other objects in Vulkan, the micromap creation merely creates an object with a specific “shape”. The type and quantity of geometry that can be built into a micromap is determined by the parameters of MicromapCreateInfoEXT.

Populating the data in the object after allocating and binding memory is done with commands such as cmdBuildMicromapsEXT, buildMicromapsEXT, cmdCopyMicromapEXT, and copyMicromapEXT.

The input buffers passed to micromap build commands will be referenced by the implementation for the duration of the command. Micromaps must be fully self-contained. The application may re-use or free any memory which was used by the command as an input or as scratch without affecting the results of a subsequent acceleration structure build using the micromap or traversal of that acceleration structure.

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

VK_EXT_opacity_micromap, AllocationCallbacks, Device, MicromapCreateInfoEXT, MicromapEXT

withMicromapEXT :: forall io r. MonadIO io => Device -> MicromapCreateInfoEXT -> Maybe AllocationCallbacks -> (io MicromapEXT -> (MicromapEXT -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createMicromapEXT and destroyMicromapEXT

To ensure that destroyMicromapEXT 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.

cmdBuildMicromapsEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command will be recorded.

-> ("infos" ::: Vector MicromapBuildInfoEXT)

pInfos is a pointer to an array of infoCount MicromapBuildInfoEXT structures defining the data used to build each micromap.

-> io () 

vkCmdBuildMicromapsEXT - Build a micromap

Description

The cmdBuildMicromapsEXT command provides the ability to initiate multiple micromaps builds, however there is no ordering or synchronization implied between any of the individual micromap builds.

Note

This means that there cannot be any memory aliasing between any micromap memories or scratch memories being used by any of the builds.

Accesses to the micromap scratch buffers as identified by the MicromapBuildInfoEXT::scratchData buffer device addresses must be synchronized with the PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT pipeline stage and an access type of ACCESS_2_MICROMAP_READ_BIT_EXT or ACCESS_2_MICROMAP_WRITE_BIT_EXT. Similarly for accesses to MicromapBuildInfoEXT::dstMicromap.

Accesses to other input buffers as identified by any used values of MicromapBuildInfoEXT::data or MicromapBuildInfoEXT::triangleArray must be synchronized with the PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT pipeline stage and an access type of ACCESS_SHADER_READ_BIT.

Valid Usage

  • For each pInfos[i], dstMicromap must have been created with a value of MicromapCreateInfoEXT::size greater than or equal to the memory size required by the build operation, as returned by getMicromapBuildSizesEXT with pBuildInfo = pInfos[i]
  • The mode member of each element of pInfos must be a valid BuildMicromapModeEXT value
  • The dstMicromap member of any element of pInfos must be a valid MicromapEXT handle
  • For each element of pInfos its type member must match the value of MicromapCreateInfoEXT::type when its dstMicromap was created
  • The range of memory backing the dstMicromap member of any element of pInfos that is accessed by this command must not overlap the memory backing the dstMicromap member of any other element of pInfos, which is accessed by this command
  • The range of memory backing the dstMicromap member of any element of pInfos that is accessed by this command must not overlap the memory backing the scratchData member of any element of pInfos (including the same element), which is accessed by this command
  • The range of memory backing the scratchData member of any element of pInfos that is accessed by this command must not overlap the memory backing the scratchData member of any other element of pInfos, which is accessed by this command
  • For each element of pInfos, the buffer used to create its dstMicromap member must be bound to device memory
  • If pInfos[i].mode is BUILD_MICROMAP_MODE_BUILD_EXT, all addresses between pInfos[i].scratchData.deviceAddress and pInfos[i].scratchData.deviceAddress + N - 1 must be in the buffer device address range of the same buffer, where N is given by the buildScratchSize member of the MicromapBuildSizesInfoEXT structure returned from a call to getMicromapBuildSizesEXT with an identical MicromapBuildInfoEXT structure and primitive count
  • The buffers from which the buffer device addresses for all of the data and triangleArray members of all pInfos[i] are queried must have been created with the BUFFER_USAGE_MICROMAP_BUILD_INPUT_READ_ONLY_BIT_EXT usage flag
  • For each element of pInfos[i] the buffer from which the buffer device address pInfos[i].scratchData.deviceAddress is queried must have been created with BUFFER_USAGE_STORAGE_BUFFER_BIT usage flag
  • For each element of pInfos, its scratchData.deviceAddress, data.deviceAddress, and triangleArray.deviceAddress members must be valid device addresses obtained from getBufferDeviceAddress
  • For each element of pInfos, if scratchData.deviceAddress, data.deviceAddress, or triangleArray.deviceAddress is the address of a non-sparse buffer then it must be bound completely and contiguously to a single DeviceMemory object
  • For each element of pInfos, its scratchData.deviceAddress member must be a multiple of PhysicalDeviceAccelerationStructurePropertiesKHR::minAccelerationStructureScratchOffsetAlignment
  • For each element of pInfos, its triangleArray.deviceAddress and data.deviceAddress members must be a multiple of 256

Valid Usage (Implicit)

  • pInfos must be a valid pointer to an array of infoCount valid MicromapBuildInfoEXT structures
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support compute operations
  • This command must only be called outside of a render pass instance
  • This command must only be called outside of a video coding scope
  • infoCount must be greater than 0

Host Synchronization

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

Command Properties

'

Command Buffer LevelsRender Pass ScopeVideo Coding ScopeSupported Queue TypesCommand Type
Primary SecondaryOutside Outside Compute Action

See Also

VK_EXT_opacity_micromap, CommandBuffer, MicromapBuildInfoEXT

buildMicromapsEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the Device for which the micromaps are being built.

-> DeferredOperationKHR

deferredOperation is an optional DeferredOperationKHR to request deferral for this command.

-> ("infos" ::: Vector MicromapBuildInfoEXT)

pInfos is a pointer to an array of infoCount MicromapBuildInfoEXT structures defining the geometry used to build each micromap.

-> io Result 

vkBuildMicromapsEXT - Build a micromap on the host

Description

This command fulfills the same task as cmdBuildMicromapsEXT but is executed by the host.

The buildMicromapsEXT command provides the ability to initiate multiple micromaps builds, however there is no ordering or synchronization implied between any of the individual micromap builds.

Note

This means that there cannot be any memory aliasing between any micromap memories or scratch memories being used by any of the builds.

Valid Usage

  • For each pInfos[i], dstMicromap must have been created with a value of MicromapCreateInfoEXT::size greater than or equal to the memory size required by the build operation, as returned by getMicromapBuildSizesEXT with pBuildInfo = pInfos[i]
  • The mode member of each element of pInfos must be a valid BuildMicromapModeEXT value
  • The dstMicromap member of any element of pInfos must be a valid MicromapEXT handle
  • For each element of pInfos its type member must match the value of MicromapCreateInfoEXT::type when its dstMicromap was created
  • The range of memory backing the dstMicromap member of any element of pInfos that is accessed by this command must not overlap the memory backing the dstMicromap member of any other element of pInfos, which is accessed by this command
  • The range of memory backing the dstMicromap member of any element of pInfos that is accessed by this command must not overlap the memory backing the scratchData member of any element of pInfos (including the same element), which is accessed by this command
  • The range of memory backing the scratchData member of any element of pInfos that is accessed by this command must not overlap the memory backing the scratchData member of any other element of pInfos, which is accessed by this command
  • For each element of pInfos, the buffer used to create its dstMicromap member must be bound to host-visible device memory
  • For each element of pInfos, all referenced addresses of pInfos[i].data.hostAddress must be valid host memory
  • For each element of pInfos, all referenced addresses of pInfos[i].triangleArray.hostAddress must be valid host memory
  • The ::micromapHostCommands feature must be enabled
  • If pInfos[i].mode is BUILD_MICROMAP_MODE_BUILD_EXT, all addresses between pInfos[i].scratchData.hostAddress and pInfos[i].scratchData.hostAddress + N - 1 must be valid host memory, where N is given by the buildScratchSize member of the MicromapBuildSizesInfoEXT structure returned from a call to getMicromapBuildSizesEXT with an identical MicromapBuildInfoEXT structure and primitive count
  • For each element of pInfos, the buffer used to create its dstMicromap member must be bound to memory that was not allocated with multiple instances

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If deferredOperation is not NULL_HANDLE, deferredOperation must be a valid DeferredOperationKHR handle
  • pInfos must be a valid pointer to an array of infoCount valid MicromapBuildInfoEXT structures
  • infoCount must be greater than 0
  • If deferredOperation is a valid handle, it must have been created, allocated, or retrieved from device

Return Codes

Success
Failure

See Also

VK_EXT_opacity_micromap, DeferredOperationKHR, Device, MicromapBuildInfoEXT

destroyMicromapEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the micromap.

-> MicromapEXT

micromap is the micromap to destroy.

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

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

-> io () 

vkDestroyMicromapEXT - Destroy a micromap object

Valid Usage

  • All submitted commands that refer to micromap must have completed execution
  • If AllocationCallbacks were provided when micromap was created, a compatible set of callbacks must be provided here
  • If no AllocationCallbacks were provided when micromap was created, pAllocator must be NULL

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to micromap must be externally synchronized

See Also

VK_EXT_opacity_micromap, AllocationCallbacks, Device, MicromapEXT

cmdCopyMicromapEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command will be recorded.

-> CopyMicromapInfoEXT

pInfo is a pointer to a CopyMicromapInfoEXT structure defining the copy operation.

-> io () 

vkCmdCopyMicromapEXT - Copy a micromap

Description

This command copies the pInfo->src micromap to the pInfo->dst micromap in the manner specified by pInfo->mode.

Accesses to pInfo->src and pInfo->dst must be synchronized with the PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT pipeline stage and an access type of ACCESS_2_MICROMAP_READ_BIT_EXT or ACCESS_2_MICROMAP_WRITE_BIT_EXT as appropriate.

Valid Usage

  • The buffer used to create pInfo->src must be bound to device memory
  • The buffer used to create pInfo->dst must be bound to device memory

Valid Usage (Implicit)

  • pInfo must be a valid pointer to a valid CopyMicromapInfoEXT structure
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support compute operations
  • This command must only be called outside of a render pass instance
  • This command must only be called outside of a video coding scope

Host Synchronization

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

Command Properties

'

Command Buffer LevelsRender Pass ScopeVideo Coding ScopeSupported Queue TypesCommand Type
Primary SecondaryOutside Outside Compute Action

See Also

VK_EXT_opacity_micromap, CommandBuffer, CopyMicromapInfoEXT

copyMicromapEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device which owns the micromaps.

-> DeferredOperationKHR

deferredOperation is an optional DeferredOperationKHR to request deferral for this command.

-> CopyMicromapInfoEXT

pInfo is a pointer to a CopyMicromapInfoEXT structure defining the copy operation.

-> io Result 

vkCopyMicromapEXT - Copy a micromap on the host

Description

This command fulfills the same task as cmdCopyMicromapEXT but is executed by the host.

Valid Usage

  • Any previous deferred operation that was associated with deferredOperation must be complete
  • The buffer used to create pInfo->src must be bound to host-visible device memory
  • The buffer used to create pInfo->dst must be bound to host-visible device memory
  • The ::micromapHostCommands feature must be enabled
  • The buffer used to create pInfo->src must be bound to memory that was not allocated with multiple instances
  • The buffer used to create pInfo->dst must be bound to memory that was not allocated with multiple instances

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If deferredOperation is not NULL_HANDLE, deferredOperation must be a valid DeferredOperationKHR handle
  • pInfo must be a valid pointer to a valid CopyMicromapInfoEXT structure
  • If deferredOperation is a valid handle, it must have been created, allocated, or retrieved from device

Return Codes

Success
Failure

See Also

VK_EXT_opacity_micromap, CopyMicromapInfoEXT, DeferredOperationKHR, Device

cmdCopyMicromapToMemoryEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command will be recorded.

-> CopyMicromapToMemoryInfoEXT

pInfo is an a pointer to a CopyMicromapToMemoryInfoEXT structure defining the copy operation.

-> io () 

vkCmdCopyMicromapToMemoryEXT - Copy a micromap to device memory

Description

Accesses to pInfo->src must be synchronized with the PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT pipeline stage and an access type of ACCESS_2_MICROMAP_READ_BIT_EXT. Accesses to the buffer indicated by pInfo->dst.deviceAddress must be synchronized with the PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT pipeline stage and an access type of ACCESS_TRANSFER_WRITE_BIT.

This command produces the same results as copyMicromapToMemoryEXT, but writes its result to a device address, and is executed on the device rather than the host. The output may not necessarily be bit-for-bit identical, but it can be equally used by either cmdCopyMemoryToMicromapEXT or copyMemoryToMicromapEXT.

The defined header structure for the serialized data consists of:

Valid Usage

  • pInfo->dst.deviceAddress must be a valid device address for a buffer bound to device memory
  • pInfo->dst.deviceAddress must be aligned to 256 bytes
  • If the buffer pointed to by pInfo->dst.deviceAddress is non-sparse then it must be bound completely and contiguously to a single DeviceMemory object
  • The buffer used to create pInfo->src must be bound to device memory

Valid Usage (Implicit)

  • pInfo must be a valid pointer to a valid CopyMicromapToMemoryInfoEXT structure
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support compute operations
  • This command must only be called outside of a render pass instance
  • This command must only be called outside of a video coding scope

Host Synchronization

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

Command Properties

'

Command Buffer LevelsRender Pass ScopeVideo Coding ScopeSupported Queue TypesCommand Type
Primary SecondaryOutside Outside Compute Action

See Also

VK_EXT_opacity_micromap, CommandBuffer, CopyMicromapToMemoryInfoEXT

copyMicromapToMemoryEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device which owns pInfo->src.

-> DeferredOperationKHR

deferredOperation is an optional DeferredOperationKHR to request deferral for this command.

-> CopyMicromapToMemoryInfoEXT

pInfo is a pointer to a CopyMicromapToMemoryInfoEXT structure defining the copy operation.

-> io Result 

vkCopyMicromapToMemoryEXT - Serialize a micromap on the host

Description

This command fulfills the same task as cmdCopyMicromapToMemoryEXT but is executed by the host.

This command produces the same results as cmdCopyMicromapToMemoryEXT, but writes its result directly to a host pointer, and is executed on the host rather than the device. The output may not necessarily be bit-for-bit identical, but it can be equally used by either cmdCopyMemoryToMicromapEXT or copyMemoryToMicromapEXT.

Valid Usage

  • Any previous deferred operation that was associated with deferredOperation must be complete
  • The buffer used to create pInfo->src must be bound to host-visible device memory
  • pInfo->dst.hostAddress must be a valid host pointer
  • pInfo->dst.hostAddress must be aligned to 16 bytes
  • The ::micromapHostCommands feature must be enabled
  • The buffer used to create pInfo->src must be bound to memory that was not allocated with multiple instances

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

VK_EXT_opacity_micromap, CopyMicromapToMemoryInfoEXT, DeferredOperationKHR, Device

cmdCopyMemoryToMicromapEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command will be recorded.

-> CopyMemoryToMicromapInfoEXT

pInfo is a pointer to a CopyMicromapToMemoryInfoEXT structure defining the copy operation.

-> io () 

vkCmdCopyMemoryToMicromapEXT - Copy device memory to a micromap

Description

Accesses to pInfo->dst must be synchronized with the PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT pipeline stage and an access type of ACCESS_2_MICROMAP_READ_BIT_EXT. Accesses to the buffer indicated by pInfo->src.deviceAddress must be synchronized with the PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT pipeline stage and an access type of ACCESS_TRANSFER_READ_BIT.

This command can accept micromaps produced by either cmdCopyMicromapToMemoryEXT or copyMicromapToMemoryEXT.

Valid Usage

  • pInfo->src.deviceAddress must be a valid device address for a buffer bound to device memory
  • pInfo->src.deviceAddress must be aligned to 256 bytes
  • If the buffer pointed to by pInfo->src.deviceAddress is non-sparse then it must be bound completely and contiguously to a single DeviceMemory object
  • The buffer used to create pInfo->dst must be bound to device memory

Valid Usage (Implicit)

  • pInfo must be a valid pointer to a valid CopyMemoryToMicromapInfoEXT structure
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support compute operations
  • This command must only be called outside of a render pass instance
  • This command must only be called outside of a video coding scope

Host Synchronization

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

Command Properties

'

Command Buffer LevelsRender Pass ScopeVideo Coding ScopeSupported Queue TypesCommand Type
Primary SecondaryOutside Outside Compute Action

See Also

VK_EXT_opacity_micromap, CommandBuffer, CopyMemoryToMicromapInfoEXT

copyMemoryToMicromapEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device which owns pInfo->dst.

-> DeferredOperationKHR

deferredOperation is an optional DeferredOperationKHR to request deferral for this command.

-> CopyMemoryToMicromapInfoEXT

pInfo is a pointer to a CopyMemoryToMicromapInfoEXT structure defining the copy operation.

-> io Result 

vkCopyMemoryToMicromapEXT - Deserialize a micromap on the host

Description

This command fulfills the same task as cmdCopyMemoryToMicromapEXT but is executed by the host.

This command can accept micromaps produced by either cmdCopyMicromapToMemoryEXT or copyMicromapToMemoryEXT.

Valid Usage

  • Any previous deferred operation that was associated with deferredOperation must be complete
  • pInfo->src.hostAddress must be a valid host pointer
  • pInfo->src.hostAddress must be aligned to 16 bytes
  • The buffer used to create pInfo->dst must be bound to host-visible device memory
  • The ::micromapHostCommands feature must be enabled
  • The buffer used to create pInfo->dst must be bound to memory that was not allocated with multiple instances

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

VK_EXT_opacity_micromap, CopyMemoryToMicromapInfoEXT, DeferredOperationKHR, Device

cmdWriteMicromapsPropertiesEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer into which the command will be recorded.

-> ("micromaps" ::: Vector MicromapEXT)

pMicromaps is a pointer to an array of existing previously built micromaps.

-> QueryType

queryType is a QueryType value specifying the type of queries managed by the pool.

-> QueryPool

queryPool is the query pool that will manage the results of the query.

-> ("firstQuery" ::: Word32)

firstQuery is the first query index within the query pool that will contain the micromapCount number of results.

-> io () 

vkCmdWriteMicromapsPropertiesEXT - Write micromap result parameters to query results.

Description

Accesses to any of the micromaps listed in pMicromaps must be synchronized with the PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT pipeline stage and an access type of ACCESS_2_MICROMAP_READ_BIT_EXT.

Valid Usage

  • queryPool must have been created with a queryType matching queryType

Valid Usage (Implicit)

  • pMicromaps must be a valid pointer to an array of micromapCount valid MicromapEXT handles
  • queryType must be a valid QueryType value
  • queryPool must be a valid QueryPool handle
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support compute operations
  • This command must only be called outside of a render pass instance
  • This command must only be called outside of a video coding scope
  • micromapCount must be greater than 0
  • Each of commandBuffer, queryPool, and the elements of pMicromaps must have been created, allocated, or retrieved from the same Device

Host Synchronization

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

Command Properties

'

Command Buffer LevelsRender Pass ScopeVideo Coding ScopeSupported Queue TypesCommand Type
Primary SecondaryOutside Outside Compute Action

See Also

VK_EXT_opacity_micromap, CommandBuffer, MicromapEXT, QueryPool, QueryType

writeMicromapsPropertiesEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device which owns the micromaps in pMicromaps.

-> ("micromaps" ::: Vector MicromapEXT)

pMicromaps is a pointer to an array of existing previously built micromaps.

-> QueryType

queryType is a QueryType value specifying the property to be queried.

-> ("dataSize" ::: Word64)

dataSize is the size in bytes of the buffer pointed to by pData.

-> ("data" ::: Ptr ())

pData is a pointer to a user-allocated buffer where the results will be written.

-> ("stride" ::: Word64)

stride is the stride in bytes between results for individual queries within pData.

-> io () 

vkWriteMicromapsPropertiesEXT - Query micromap meta-data on the host

Description

This command fulfills the same task as cmdWriteMicromapsPropertiesEXT but is executed by the host.

Valid Usage

  • All micromaps in pMicromaps must have been constructed prior to the execution of this command

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pMicromaps must be a valid pointer to an array of micromapCount valid MicromapEXT handles
  • queryType must be a valid QueryType value
  • pData must be a valid pointer to an array of dataSize bytes
  • micromapCount must be greater than 0
  • dataSize must be greater than 0
  • Each element of pMicromaps must have been created, allocated, or retrieved from device

Return Codes

Success
Failure

See Also

VK_EXT_opacity_micromap, Device, MicromapEXT, QueryType

getDeviceMicromapCompatibilityEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device to check the version against.

-> MicromapVersionInfoEXT

pVersionInfo is a pointer to a MicromapVersionInfoEXT structure specifying version information to check against the device.

-> io AccelerationStructureCompatibilityKHR 

vkGetDeviceMicromapCompatibilityEXT - Check if a serialized micromap is compatible with the current device

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle

See Also

VK_EXT_opacity_micromap, AccelerationStructureCompatibilityKHR, Device, MicromapVersionInfoEXT

getMicromapBuildSizesEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that will be used for creating the micromap.

-> AccelerationStructureBuildTypeKHR

buildType defines whether host or device operations (or both) are being queried for.

-> MicromapBuildInfoEXT

pBuildInfo is a pointer to a MicromapBuildInfoEXT structure describing parameters of a build operation.

-> io ("sizeInfo" ::: MicromapBuildSizesInfoEXT) 

vkGetMicromapBuildSizesEXT - Retrieve the required size for a micromap

Description

The dstMicromap and mode members of pBuildInfo are ignored. Any DeviceOrHostAddressKHR members of pBuildInfo are ignored by this command.

A micromap created with the micromapSize returned by this command supports any build with a MicromapBuildInfoEXT structure subject to the following properties:

Similarly, the buildScratchSize value will support any build command specifying the BUILD_MICROMAP_MODE_BUILD_EXT mode under the above conditions.

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle

See Also

VK_EXT_opacity_micromap, AccelerationStructureBuildTypeKHR, Device, MicromapBuildInfoEXT, MicromapBuildSizesInfoEXT

data MicromapBuildInfoEXT Source #

VkMicromapBuildInfoEXT - Structure specifying the data used to build a micromap

Description

Only one of pUsageCounts or ppUsageCounts can be a valid pointer, the other must be NULL. The elements of the non-NULL array describe the total counts used to build each micromap. Each element contains a count which is the number of micromap triangles of that format and subdivisionLevel contained in the micromap. Multiple elements with the same format and subdivisionLevel are allowed and the total count for that format and subdivisionLevel is the sum of the count for each element.

Each micromap triangle refers to one element in triangleArray which contains the format and subdivisionLevel for that particular triangle as well as a dataOffset in bytes which is the location relative to data where that triangle’s micromap data begins. The data at triangleArray is laid out as a 4 byte unsigned integer for the dataOffset followed by a 2 byte unsigned integer for the subdivision level then a 2 byte unsigned integer for the format. In practice, compilers compile MicromapTriangleEXT to match this pattern.

The data at data is packed as either one bit per element for OPACITY_MICROMAP_FORMAT_2_STATE_EXT or two bits per element for OPACITY_MICROMAP_FORMAT_4_STATE_EXT and is packed from LSB to MSB in each byte. The data at each index in those bytes is interpreted as discussed in Ray Opacity Micromap.

Valid Usage

  • Only one of pUsageCounts or ppUsageCounts can be a valid pointer, the other must be NULL.

Valid Usage (Implicit)

  • pNext must be NULL
  • type must be a valid MicromapTypeEXT value
  • flags must be a valid combination of BuildMicromapFlagBitsEXT values
  • If usageCountsCount is not 0, and pUsageCounts is not NULL, pUsageCounts must be a valid pointer to an array of usageCountsCount MicromapUsageEXT structures
  • If usageCountsCount is not 0, and ppUsageCounts is not NULL, ppUsageCounts must be a valid pointer to an array of usageCountsCount valid pointers to MicromapUsageEXT structures

See Also

VK_EXT_opacity_micromap, BuildMicromapFlagsEXT, BuildMicromapModeEXT, DeviceOrHostAddressConstKHR, DeviceOrHostAddressKHR, DeviceSize, MicromapEXT, MicromapTypeEXT, MicromapUsageEXT, StructureType, buildMicromapsEXT, cmdBuildMicromapsEXT, getMicromapBuildSizesEXT

Constructors

MicromapBuildInfoEXT 

Fields

data MicromapCreateInfoEXT Source #

VkMicromapCreateInfoEXT - Structure specifying the parameters of a newly created micromap object

Description

If deviceAddress is zero, no specific address is requested.

If deviceAddress is not zero, deviceAddress must be an address retrieved from an identically created micromap on the same implementation. The micromap must also be placed on an identically created buffer and at the same offset.

Applications should avoid creating micromaps with application-provided addresses and implementation-provided addresses in the same process, to reduce the likelihood of ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS_KHR errors.

Note

The expected usage for this is that a trace capture/replay tool will add the BUFFER_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT flag to all buffers that use BUFFER_USAGE_SHADER_DEVICE_ADDRESS_BIT, and will add BUFFER_USAGE_SHADER_DEVICE_ADDRESS_BIT to all buffers used as storage for a micromap where deviceAddress is not zero. This also means that the tool will need to add MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT to memory allocations to allow the flag to be set where the application may not have otherwise required it. During capture the tool will save the queried opaque device addresses in the trace. During replay, the buffers will be created specifying the original address so any address values stored in the trace data will remain valid.

Implementations are expected to separate such buffers in the GPU address space so normal allocations will avoid using these addresses. Apps/tools should avoid mixing app-provided and implementation-provided addresses for buffers created with BUFFER_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT, to avoid address space allocation conflicts.

If the micromap will be the target of a build operation, the required size for a micromap can be queried with getMicromapBuildSizesEXT.

Valid Usage

Valid Usage (Implicit)

See Also

VK_EXT_opacity_micromap, Buffer, DeviceAddress, DeviceSize, MicromapCreateFlagsEXT, MicromapTypeEXT, StructureType, createMicromapEXT

Constructors

MicromapCreateInfoEXT 

Fields

Instances

Instances details
Storable MicromapCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show MicromapCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq MicromapCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

FromCStruct MicromapCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

ToCStruct MicromapCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero MicromapCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

data MicromapVersionInfoEXT Source #

VkMicromapVersionInfoEXT - Micromap version information

Description

Note

pVersionData is a pointer to an array of 2×UUID_SIZE uint8_t values instead of two UUID_SIZE arrays as the expected use case for this member is to be pointed at the header of a previously serialized micromap (via cmdCopyMicromapToMemoryEXT or copyMicromapToMemoryEXT) that is loaded in memory. Using arrays would necessitate extra memory copies of the UUIDs.

Valid Usage (Implicit)

See Also

VK_EXT_opacity_micromap, StructureType, getDeviceMicromapCompatibilityEXT

Constructors

MicromapVersionInfoEXT 

Fields

data CopyMicromapInfoEXT Source #

VkCopyMicromapInfoEXT - Parameters for copying a micromap

Valid Usage

  • The source acceleration structure src must have been constructed prior to the execution of this command
  • If mode is COPY_MICROMAP_MODE_COMPACT_EXT, src must have been constructed with BUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT in the build
  • The buffer used to create src must be bound to device memory
  • The buffer used to create dst must be bound to device memory

Valid Usage (Implicit)

See Also

VK_EXT_opacity_micromap, CopyMicromapModeEXT, MicromapEXT, StructureType, cmdCopyMicromapEXT, copyMicromapEXT

Constructors

CopyMicromapInfoEXT 

Fields

Instances

Instances details
Storable CopyMicromapInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show CopyMicromapInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq CopyMicromapInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

FromCStruct CopyMicromapInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

ToCStruct CopyMicromapInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero CopyMicromapInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

data CopyMicromapToMemoryInfoEXT Source #

VkCopyMicromapToMemoryInfoEXT - Parameters for serializing a micromap

Valid Usage

  • The source micromap src must have been constructed prior to the execution of this command

Valid Usage (Implicit)

See Also

VK_EXT_opacity_micromap, CopyMicromapModeEXT, DeviceOrHostAddressKHR, MicromapEXT, StructureType, cmdCopyMicromapToMemoryEXT, copyMicromapToMemoryEXT

Constructors

CopyMicromapToMemoryInfoEXT 

Fields

data CopyMemoryToMicromapInfoEXT Source #

VkCopyMemoryToMicromapInfoEXT - Parameters for deserializing a micromap

Valid Usage

Valid Usage (Implicit)

See Also

VK_EXT_opacity_micromap, CopyMicromapModeEXT, DeviceOrHostAddressConstKHR, MicromapEXT, StructureType, cmdCopyMemoryToMicromapEXT, copyMemoryToMicromapEXT

Constructors

CopyMemoryToMicromapInfoEXT 

Fields

data MicromapBuildSizesInfoEXT Source #

VkMicromapBuildSizesInfoEXT - Structure specifying build sizes for a micromap

Valid Usage (Implicit)

See Also

VK_EXT_opacity_micromap, Bool32, DeviceSize, StructureType, getMicromapBuildSizesEXT

Constructors

MicromapBuildSizesInfoEXT 

Fields

  • micromapSize :: DeviceSize

    micromapSize is the size in bytes required in a MicromapEXT for a build or update operation.

  • buildScratchSize :: DeviceSize

    buildScratchSize is the size in bytes required in a scratch buffer for a build operation.

  • discardable :: Bool

    discardable indicates whether or not the micromap object may be destroyed after an acceleration structure build or update. A false value means that acceleration structures built with this micromap may contain references to the data contained therein, and the application must not destroy the micromap until ray traversal has concluded. A true value means that the information in the micromap will be copied by value into the acceleration structure, and the micromap may be destroyed after the acceleration structure build concludes.

Instances

Instances details
Storable MicromapBuildSizesInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show MicromapBuildSizesInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq MicromapBuildSizesInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

FromCStruct MicromapBuildSizesInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

ToCStruct MicromapBuildSizesInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero MicromapBuildSizesInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

data MicromapUsageEXT Source #

VkMicromapUsageEXT - Structure specifying the usage information used to build a micromap

Valid Usage

The format is interpreted based on the type of the micromap using it.

See Also

VK_EXT_opacity_micromap, AccelerationStructureTrianglesOpacityMicromapEXT, MicromapBuildInfoEXT

Constructors

MicromapUsageEXT 

Fields

  • count :: Word32

    count is the number of triangles in the usage format defined by the subdivisionLevel and format below in the micromap

  • subdivisionLevel :: Word32

    subdivisionLevel is the subdivision level of this usage format

  • format :: Word32

    format is the format of this usage format

Instances

Instances details
Storable MicromapUsageEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show MicromapUsageEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq MicromapUsageEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

FromCStruct MicromapUsageEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

ToCStruct MicromapUsageEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero MicromapUsageEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

data MicromapTriangleEXT Source #

VkMicromapTriangleEXT - Structure specifying the micromap format and data for a triangle

Valid Usage

The format is interpreted based on the type of the micromap using it.

See Also

VK_EXT_opacity_micromap

Constructors

MicromapTriangleEXT 

Fields

  • dataOffset :: Word32

    dataOffset is the offset in bytes of the start of the data for this triangle. This is a byte aligned value.

  • subdivisionLevel :: Word16

    subdivisionLevel is the subdivision level of this triangle

  • format :: Word16

    format is the format of this triangle

Instances

Instances details
Storable MicromapTriangleEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show MicromapTriangleEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq MicromapTriangleEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

FromCStruct MicromapTriangleEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

ToCStruct MicromapTriangleEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero MicromapTriangleEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

data PhysicalDeviceOpacityMicromapFeaturesEXT Source #

VkPhysicalDeviceOpacityMicromapFeaturesEXT - Structure describing the ray tracing opacity micromap features that can be supported by an implementation

Members

This structure describes the following feature:

Description

If the PhysicalDeviceOpacityMicromapFeaturesEXT structure is included in the pNext chain of the PhysicalDeviceFeatures2 structure passed to getPhysicalDeviceFeatures2, it is filled in to indicate whether each corresponding feature is supported. PhysicalDeviceOpacityMicromapFeaturesEXT can also be used in the pNext chain of DeviceCreateInfo to selectively enable these features.

Valid Usage (Implicit)

See Also

VK_EXT_opacity_micromap, Bool32, StructureType

Constructors

PhysicalDeviceOpacityMicromapFeaturesEXT 

Fields

  • micromap :: Bool

    micromap indicates whether the implementation supports the micromap array feature.

  • micromapCaptureReplay :: Bool

    micromapCaptureReplay indicates whether the implementation supports capture and replay of addresses for micromap arrays.

  • micromapHostCommands :: Bool

    micromapHostCommands indicates whether the implementation supports host side micromap array commands.

Instances

Instances details
Storable PhysicalDeviceOpacityMicromapFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show PhysicalDeviceOpacityMicromapFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq PhysicalDeviceOpacityMicromapFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

FromCStruct PhysicalDeviceOpacityMicromapFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

ToCStruct PhysicalDeviceOpacityMicromapFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero PhysicalDeviceOpacityMicromapFeaturesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

data PhysicalDeviceOpacityMicromapPropertiesEXT Source #

VkPhysicalDeviceOpacityMicromapPropertiesEXT - Structure describing the opacity micromap properties of a physical device

Description

If the PhysicalDeviceOpacityMicromapPropertiesEXT structure is included in the pNext chain of the PhysicalDeviceProperties2 structure passed to getPhysicalDeviceProperties2, it is filled in with each corresponding implementation-dependent property.

Valid Usage (Implicit)

See Also

VK_EXT_opacity_micromap, StructureType

Constructors

PhysicalDeviceOpacityMicromapPropertiesEXT 

Fields

Instances

Instances details
Storable PhysicalDeviceOpacityMicromapPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show PhysicalDeviceOpacityMicromapPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq PhysicalDeviceOpacityMicromapPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

FromCStruct PhysicalDeviceOpacityMicromapPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

ToCStruct PhysicalDeviceOpacityMicromapPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero PhysicalDeviceOpacityMicromapPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

data AccelerationStructureTrianglesOpacityMicromapEXT Source #

VkAccelerationStructureTrianglesOpacityMicromapEXT - Structure specifying an opacity micromap in a bottom-level acceleration structure

Description

If AccelerationStructureTrianglesOpacityMicromapEXT is included in the pNext chain of a AccelerationStructureGeometryTrianglesDataKHR structure, that geometry will reference that micromap.

For each triangle in the geometry, the acceleration structure build fetches an index from indexBuffer using indexType and indexStride. If that value is the unsigned cast of one of the values from OpacityMicromapSpecialIndexEXT then that triangle behaves as described for that special value in Ray Opacity Micromap. Otherwise that triangle uses the opacity micromap information from micromap at that index plus baseTriangle.

Only one of pUsageCounts or ppUsageCounts can be a valid pointer, the other must be NULL. The elements of the non-NULL array describe the total count used to build this geometry. For a given format and subdivisionLevel the number of triangles in this geometry matching those values after indirection and special index handling must be equal to the sum of matching count provided.

If micromap is NULL_HANDLE, then every value read from indexBuffer must be one of the values in OpacityMicromapSpecialIndexEXT.

Valid Usage

  • Only one of pUsageCounts or ppUsageCounts can be a valid pointer, the other must be NULL.

Valid Usage (Implicit)

  • indexType must be a valid IndexType value
  • If usageCountsCount is not 0, and pUsageCounts is not NULL, pUsageCounts must be a valid pointer to an array of usageCountsCount MicromapUsageEXT structures
  • If usageCountsCount is not 0, and ppUsageCounts is not NULL, ppUsageCounts must be a valid pointer to an array of usageCountsCount valid pointers to MicromapUsageEXT structures
  • micromap must be a valid MicromapEXT handle

See Also

VK_EXT_opacity_micromap, DeviceOrHostAddressConstKHR, DeviceSize, IndexType, MicromapEXT, MicromapUsageEXT, StructureType

Constructors

AccelerationStructureTrianglesOpacityMicromapEXT 

Fields

newtype MicromapTypeEXT Source #

VkMicromapTypeEXT - Type of micromap

See Also

VK_EXT_opacity_micromap, MicromapBuildInfoEXT, MicromapCreateInfoEXT

Constructors

MicromapTypeEXT Int32 

Bundled Patterns

pattern MICROMAP_TYPE_OPACITY_MICROMAP_EXT :: MicromapTypeEXT

MICROMAP_TYPE_OPACITY_MICROMAP_EXT is a micromap containing data to control the opacity of a triangle

Instances

Instances details
Storable MicromapTypeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Read MicromapTypeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show MicromapTypeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq MicromapTypeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Ord MicromapTypeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero MicromapTypeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

newtype BuildMicromapFlagBitsEXT Source #

VkBuildMicromapFlagBitsEXT - Bitmask specifying additional parameters for micromap builds

See Also

VK_EXT_opacity_micromap, BuildMicromapFlagsEXT

Bundled Patterns

pattern BUILD_MICROMAP_PREFER_FAST_TRACE_BIT_EXT :: BuildMicromapFlagBitsEXT

BUILD_MICROMAP_PREFER_FAST_TRACE_BIT_EXT indicates that the given micromap build should prioritize trace performance over build time.

pattern BUILD_MICROMAP_PREFER_FAST_BUILD_BIT_EXT :: BuildMicromapFlagBitsEXT

BUILD_MICROMAP_PREFER_FAST_BUILD_BIT_EXT indicates that the given micromap build should prioritize build time over trace performance.

pattern BUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT :: BuildMicromapFlagBitsEXT 

Instances

Instances details
Bits BuildMicromapFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

FiniteBits BuildMicromapFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Storable BuildMicromapFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Read BuildMicromapFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show BuildMicromapFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq BuildMicromapFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Ord BuildMicromapFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero BuildMicromapFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

newtype MicromapCreateFlagBitsEXT Source #

VkMicromapCreateFlagBitsEXT - Bitmask specifying additional creation parameters for micromap

See Also

VK_EXT_opacity_micromap, MicromapCreateFlagsEXT

Bundled Patterns

pattern MICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT :: MicromapCreateFlagBitsEXT

MICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT specifies that the micromap’s address can be saved and reused on a subsequent run.

Instances

Instances details
Bits MicromapCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Methods

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

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

xor :: MicromapCreateFlagBitsEXT -> MicromapCreateFlagBitsEXT -> MicromapCreateFlagBitsEXT #

complement :: MicromapCreateFlagBitsEXT -> MicromapCreateFlagBitsEXT #

shift :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

rotate :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

zeroBits :: MicromapCreateFlagBitsEXT #

bit :: Int -> MicromapCreateFlagBitsEXT #

setBit :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

clearBit :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

complementBit :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

testBit :: MicromapCreateFlagBitsEXT -> Int -> Bool #

bitSizeMaybe :: MicromapCreateFlagBitsEXT -> Maybe Int #

bitSize :: MicromapCreateFlagBitsEXT -> Int #

isSigned :: MicromapCreateFlagBitsEXT -> Bool #

shiftL :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

unsafeShiftL :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

shiftR :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

unsafeShiftR :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

rotateL :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

rotateR :: MicromapCreateFlagBitsEXT -> Int -> MicromapCreateFlagBitsEXT #

popCount :: MicromapCreateFlagBitsEXT -> Int #

FiniteBits MicromapCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Storable MicromapCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Read MicromapCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show MicromapCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq MicromapCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Ord MicromapCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero MicromapCreateFlagBitsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

newtype CopyMicromapModeEXT Source #

Bundled Patterns

pattern COPY_MICROMAP_MODE_CLONE_EXT :: CopyMicromapModeEXT

COPY_MICROMAP_MODE_CLONE_EXT creates a direct copy of the micromap specified in src into the one specified by dst. The dst micromap must have been created with the same parameters as src.

pattern COPY_MICROMAP_MODE_SERIALIZE_EXT :: CopyMicromapModeEXT

COPY_MICROMAP_MODE_SERIALIZE_EXT serializes the micromap to a semi-opaque format which can be reloaded on a compatible implementation.

pattern COPY_MICROMAP_MODE_DESERIALIZE_EXT :: CopyMicromapModeEXT

COPY_MICROMAP_MODE_DESERIALIZE_EXT deserializes the semi-opaque serialization format in the buffer to the micromap.

pattern COPY_MICROMAP_MODE_COMPACT_EXT :: CopyMicromapModeEXT

COPY_MICROMAP_MODE_COMPACT_EXT creates a more compact version of a micromap src into dst. The micromap dst must have been created with a size at least as large as that returned by cmdWriteMicromapsPropertiesEXT after the build of the micromap specified by src.

Instances

Instances details
Storable CopyMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Read CopyMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show CopyMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq CopyMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Ord CopyMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero CopyMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

newtype BuildMicromapModeEXT Source #

VkBuildMicromapModeEXT - Enum specifying the type of build operation to perform

See Also

VK_EXT_opacity_micromap, MicromapBuildInfoEXT

Bundled Patterns

pattern BUILD_MICROMAP_MODE_BUILD_EXT :: BuildMicromapModeEXT

BUILD_MICROMAP_MODE_BUILD_EXT specifies that the destination micromap will be built using the specified data.

Instances

Instances details
Storable BuildMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Read BuildMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show BuildMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq BuildMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Ord BuildMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero BuildMicromapModeEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

newtype OpacityMicromapFormatEXT Source #

VkOpacityMicromapFormatEXT - Format enum for opacity micromaps

See Also

VK_EXT_opacity_micromap

Bundled Patterns

pattern OPACITY_MICROMAP_FORMAT_2_STATE_EXT :: OpacityMicromapFormatEXT

OPACITY_MICROMAP_FORMAT_2_STATE_EXT indicates that the given micromap format has one bit per subtriangle encoding either fully opaque or fully transparent.

pattern OPACITY_MICROMAP_FORMAT_4_STATE_EXT :: OpacityMicromapFormatEXT

OPACITY_MICROMAP_FORMAT_4_STATE_EXT indicates that the given micromap format has two bits per subtriangle encoding four modes which can be interpreted as described in ray traversal.

Instances

Instances details
Storable OpacityMicromapFormatEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Read OpacityMicromapFormatEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show OpacityMicromapFormatEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq OpacityMicromapFormatEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Ord OpacityMicromapFormatEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero OpacityMicromapFormatEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

newtype OpacityMicromapSpecialIndexEXT Source #

VkOpacityMicromapSpecialIndexEXT - Enum for special indices in the opacity micromap

See Also

VK_EXT_opacity_micromap

Instances

Instances details
Storable OpacityMicromapSpecialIndexEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Read OpacityMicromapSpecialIndexEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Show OpacityMicromapSpecialIndexEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Eq OpacityMicromapSpecialIndexEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Ord OpacityMicromapSpecialIndexEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

Zero OpacityMicromapSpecialIndexEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_opacity_micromap

type EXT_OPACITY_MICROMAP_EXTENSION_NAME = "VK_EXT_opacity_micromap" Source #

pattern EXT_OPACITY_MICROMAP_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #

newtype DeferredOperationKHR Source #

Instances

Instances details
Storable DeferredOperationKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show DeferredOperationKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Eq DeferredOperationKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord DeferredOperationKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType DeferredOperationKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle DeferredOperationKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero DeferredOperationKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

newtype MicromapEXT Source #

Constructors

MicromapEXT Word64 

Instances

Instances details
Storable MicromapEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show MicromapEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Eq MicromapEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord MicromapEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType MicromapEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle MicromapEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero MicromapEXT Source # 
Instance details

Defined in Vulkan.Extensions.Handles

newtype GeometryInstanceFlagBitsKHR Source #

VkGeometryInstanceFlagBitsKHR - Instance flag bits

Description

GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR and GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR must not be used in the same flag.

See Also

VK_KHR_acceleration_structure, VK_NV_ray_tracing, GeometryInstanceFlagsKHR

Bundled Patterns

pattern GEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR :: GeometryInstanceFlagBitsKHR

GEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR disables face culling for this instance.

pattern GEOMETRY_INSTANCE_TRIANGLE_FLIP_FACING_BIT_KHR :: GeometryInstanceFlagBitsKHR

GEOMETRY_INSTANCE_TRIANGLE_FLIP_FACING_BIT_KHR indicates that the facing determination for geometry in this instance is inverted. Because the facing is determined in object space, an instance transform does not change the winding, but a geometry transform does.

pattern GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR :: GeometryInstanceFlagBitsKHR

GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR causes this instance to act as though GEOMETRY_OPAQUE_BIT_KHR were specified on all geometries referenced by this instance. This behavior can be overridden by the SPIR-V NoOpaqueKHR ray flag.

pattern GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR :: GeometryInstanceFlagBitsKHR

GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR causes this instance to act as though GEOMETRY_OPAQUE_BIT_KHR were not specified on all geometries referenced by this instance. This behavior can be overridden by the SPIR-V OpaqueKHR ray flag.

pattern GEOMETRY_INSTANCE_DISABLE_OPACITY_MICROMAPS_EXT :: GeometryInstanceFlagBitsKHR 
pattern GEOMETRY_INSTANCE_FORCE_OPACITY_MICROMAP_2_STATE_EXT :: GeometryInstanceFlagBitsKHR 

Instances

Instances details
Bits GeometryInstanceFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Methods

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

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

xor :: GeometryInstanceFlagBitsKHR -> GeometryInstanceFlagBitsKHR -> GeometryInstanceFlagBitsKHR #

complement :: GeometryInstanceFlagBitsKHR -> GeometryInstanceFlagBitsKHR #

shift :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

rotate :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

zeroBits :: GeometryInstanceFlagBitsKHR #

bit :: Int -> GeometryInstanceFlagBitsKHR #

setBit :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

clearBit :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

complementBit :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

testBit :: GeometryInstanceFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: GeometryInstanceFlagBitsKHR -> Maybe Int #

bitSize :: GeometryInstanceFlagBitsKHR -> Int #

isSigned :: GeometryInstanceFlagBitsKHR -> Bool #

shiftL :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

unsafeShiftL :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

shiftR :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

unsafeShiftR :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

rotateL :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

rotateR :: GeometryInstanceFlagBitsKHR -> Int -> GeometryInstanceFlagBitsKHR #

popCount :: GeometryInstanceFlagBitsKHR -> Int #

FiniteBits GeometryInstanceFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Storable GeometryInstanceFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Read GeometryInstanceFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Show GeometryInstanceFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Eq GeometryInstanceFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Ord GeometryInstanceFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Zero GeometryInstanceFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

newtype BuildAccelerationStructureFlagBitsKHR Source #

VkBuildAccelerationStructureFlagBitsKHR - Bitmask specifying additional parameters for acceleration structure builds

Description

Note

BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR and BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR may take more time and memory than a normal build, and so should only be used when those features are needed.

See Also

VK_KHR_acceleration_structure, VK_NV_ray_tracing, BuildAccelerationStructureFlagsKHR

Bundled Patterns

pattern BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR :: BuildAccelerationStructureFlagBitsKHR

BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR indicates that the specified acceleration structure can be updated with a mode of BUILD_ACCELERATION_STRUCTURE_MODE_UPDATE_KHR in AccelerationStructureBuildGeometryInfoKHR or an update of TRUE in cmdBuildAccelerationStructureNV .

pattern BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR :: BuildAccelerationStructureFlagBitsKHR

BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR indicates that the specified acceleration structure can act as the source for a copy acceleration structure command with mode of COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR to produce a compacted acceleration structure.

pattern BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR :: BuildAccelerationStructureFlagBitsKHR

BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR indicates that the given acceleration structure build should prioritize trace performance over build time.

pattern BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR :: BuildAccelerationStructureFlagBitsKHR

BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR indicates that the given acceleration structure build should prioritize build time over trace performance.

pattern BUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR :: BuildAccelerationStructureFlagBitsKHR

BUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR indicates that this acceleration structure should minimize the size of the scratch memory and the final result acceleration structure, potentially at the expense of build time or trace performance.

pattern BUILD_ACCELERATION_STRUCTURE_ALLOW_OPACITY_MICROMAP_DATA_UPDATE_EXT :: BuildAccelerationStructureFlagBitsKHR

BUILD_ACCELERATION_STRUCTURE_ALLOW_OPACITY_MICROMAP_DATA_UPDATE_EXT indicates that the data of the opacity micromaps associated with the specified acceleration structure may change with an acceleration structure update.

pattern BUILD_ACCELERATION_STRUCTURE_ALLOW_DISABLE_OPACITY_MICROMAPS_EXT :: BuildAccelerationStructureFlagBitsKHR

BUILD_ACCELERATION_STRUCTURE_ALLOW_DISABLE_OPACITY_MICROMAPS_EXT indicates that the specified acceleration structure may be referenced in an instance with GEOMETRY_INSTANCE_DISABLE_OPACITY_MICROMAPS_EXT set.

pattern BUILD_ACCELERATION_STRUCTURE_ALLOW_OPACITY_MICROMAP_UPDATE_EXT :: BuildAccelerationStructureFlagBitsKHR

BUILD_ACCELERATION_STRUCTURE_ALLOW_OPACITY_MICROMAP_UPDATE_EXT indicates that the opacity micromaps associated with the specified acceleration structure may change with an acceleration structure update.

pattern BUILD_ACCELERATION_STRUCTURE_MOTION_BIT_NV :: BuildAccelerationStructureFlagBitsKHR 

Instances

Instances details
Bits BuildAccelerationStructureFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Methods

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

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

xor :: BuildAccelerationStructureFlagBitsKHR -> BuildAccelerationStructureFlagBitsKHR -> BuildAccelerationStructureFlagBitsKHR #

complement :: BuildAccelerationStructureFlagBitsKHR -> BuildAccelerationStructureFlagBitsKHR #

shift :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

rotate :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

zeroBits :: BuildAccelerationStructureFlagBitsKHR #

bit :: Int -> BuildAccelerationStructureFlagBitsKHR #

setBit :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

clearBit :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

complementBit :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

testBit :: BuildAccelerationStructureFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: BuildAccelerationStructureFlagBitsKHR -> Maybe Int #

bitSize :: BuildAccelerationStructureFlagBitsKHR -> Int #

isSigned :: BuildAccelerationStructureFlagBitsKHR -> Bool #

shiftL :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

unsafeShiftL :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

shiftR :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

unsafeShiftR :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

rotateL :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

rotateR :: BuildAccelerationStructureFlagBitsKHR -> Int -> BuildAccelerationStructureFlagBitsKHR #

popCount :: BuildAccelerationStructureFlagBitsKHR -> Int #

FiniteBits BuildAccelerationStructureFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Storable BuildAccelerationStructureFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Read BuildAccelerationStructureFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Show BuildAccelerationStructureFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Eq BuildAccelerationStructureFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Ord BuildAccelerationStructureFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Zero BuildAccelerationStructureFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

newtype AccelerationStructureBuildTypeKHR Source #

VkAccelerationStructureBuildTypeKHR - Acceleration structure build type

See Also

VK_KHR_acceleration_structure, getAccelerationStructureBuildSizesKHR, getMicromapBuildSizesEXT

Bundled Patterns

pattern ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR :: AccelerationStructureBuildTypeKHR

ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR requests the memory requirement for operations performed by the host.

pattern ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR :: AccelerationStructureBuildTypeKHR

ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR requests the memory requirement for operations performed by the device.

pattern ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR :: AccelerationStructureBuildTypeKHR

ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR requests the memory requirement for operations performed by either the host, or the device.

Instances

Instances details
Storable AccelerationStructureBuildTypeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Read AccelerationStructureBuildTypeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Show AccelerationStructureBuildTypeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Eq AccelerationStructureBuildTypeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Ord AccelerationStructureBuildTypeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Zero AccelerationStructureBuildTypeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

newtype AccelerationStructureCompatibilityKHR Source #

VkAccelerationStructureCompatibilityKHR - Acceleration structure compatibility

See Also

VK_KHR_acceleration_structure, getDeviceAccelerationStructureCompatibilityKHR, getDeviceMicromapCompatibilityEXT

Bundled Patterns

pattern ACCELERATION_STRUCTURE_COMPATIBILITY_COMPATIBLE_KHR :: AccelerationStructureCompatibilityKHR

ACCELERATION_STRUCTURE_COMPATIBILITY_COMPATIBLE_KHR if the pVersionData version acceleration structure is compatible with device.

pattern ACCELERATION_STRUCTURE_COMPATIBILITY_INCOMPATIBLE_KHR :: AccelerationStructureCompatibilityKHR

ACCELERATION_STRUCTURE_COMPATIBILITY_INCOMPATIBLE_KHR if the pVersionData version acceleration structure is not compatible with device.

Instances

Instances details
Storable AccelerationStructureCompatibilityKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Read AccelerationStructureCompatibilityKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Show AccelerationStructureCompatibilityKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Eq AccelerationStructureCompatibilityKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Ord AccelerationStructureCompatibilityKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure

Zero AccelerationStructureCompatibilityKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_acceleration_structure