vulkan-3.13: Bindings to the Vulkan graphics API.
Safe HaskellNone
LanguageHaskell2010

Vulkan.Extensions.VK_NV_coverage_reduction_mode

Description

Name

VK_NV_coverage_reduction_mode - device extension

VK_NV_coverage_reduction_mode

Name String
VK_NV_coverage_reduction_mode
Extension Type
Device extension
Registered Extension Number
251
Revision
1
Extension and Version Dependencies
  • Requires Vulkan 1.0
  • Requires VK_NV_framebuffer_mixed_samples
Contact

Other Extension Metadata

Last Modified Date
2019-01-29
Contributors
  • Kedarnath Thangudu, NVIDIA
  • Jeff Bolz, NVIDIA

Description

When using a framebuffer with mixed samples, a per-fragment coverage reduction operation is performed which generates color sample coverage from the pixel coverage. This extension defines the following modes to control how this reduction is performed.

  • Merge: When there are more samples in the pixel coverage than color samples, there is an implementation-dependent association of each pixel coverage sample to a color sample. In the merge mode, the color sample coverage is computed such that only if any associated sample in the pixel coverage is covered, the color sample is covered. This is the default mode.
  • Truncate: When there are more raster samples (N) than color samples(M), there is one to one association of the first M raster samples to the M color samples; other raster samples are ignored.

When the number of raster samples is equal to the color samples, there is a one to one mapping between them in either of the above modes.

The new command getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV can be used to query the various raster, color, depth/stencil sample count and reduction mode combinations that are supported by the implementation. This extension would allow an implementation to support the behavior of both VK_NV_framebuffer_mixed_samples and VK_AMD_mixed_attachment_samples extensions simultaneously.

New Commands

New Structures

New Enums

New Bitmasks

New Enum Constants

Version History

  • Revision 1, 2019-01-29 (Kedarnath Thangudu)

    • Internal revisions

See Also

CoverageReductionModeNV, FramebufferMixedSamplesCombinationNV, PhysicalDeviceCoverageReductionModeFeaturesNV, PipelineCoverageReductionStateCreateFlagsNV, PipelineCoverageReductionStateCreateInfoNV, getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV

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

getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV Source #

Arguments

:: forall io. MonadIO io 
=> PhysicalDevice

physicalDevice is the physical device from which to query the set of combinations.

-> io (Result, "combinations" ::: Vector FramebufferMixedSamplesCombinationNV) 

vkGetPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV - Query supported sample count combinations

Description

If pCombinations is NULL, then the number of supported combinations for the given physicalDevice is returned in pCombinationCount. Otherwise, pCombinationCount must point to a variable set by the user to the number of elements in the pCombinations array, and on return the variable is overwritten with the number of values actually written to pCombinations. If the value of pCombinationCount is less than the number of combinations supported for the given physicalDevice, at most pCombinationCount values will be written to pCombinations, and INCOMPLETE will be returned instead of SUCCESS, to indicate that not all the supported values were returned.

Valid Usage (Implicit)

  • pCombinationCount must be a valid pointer to a uint32_t value
  • If the value referenced by pCombinationCount is not 0, and pCombinations is not NULL, pCombinations must be a valid pointer to an array of pCombinationCount FramebufferMixedSamplesCombinationNV structures

Return Codes

Success
Failure

See Also

VK_NV_coverage_reduction_mode, FramebufferMixedSamplesCombinationNV, PhysicalDevice

data PhysicalDeviceCoverageReductionModeFeaturesNV Source #

VkPhysicalDeviceCoverageReductionModeFeaturesNV - Structure describing the coverage reduction mode features that can be supported by an implementation

Members

This structure describes the following feature:

Description

If the PhysicalDeviceCoverageReductionModeFeaturesNV 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. PhysicalDeviceCoverageReductionModeFeaturesNV can also be used in the pNext chain of DeviceCreateInfo to selectively enable these features.

Valid Usage (Implicit)

See Also

VK_NV_coverage_reduction_mode, Bool32, StructureType

Constructors

PhysicalDeviceCoverageReductionModeFeaturesNV 

Fields

Instances

Instances details
Eq PhysicalDeviceCoverageReductionModeFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Show PhysicalDeviceCoverageReductionModeFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Storable PhysicalDeviceCoverageReductionModeFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

FromCStruct PhysicalDeviceCoverageReductionModeFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

ToCStruct PhysicalDeviceCoverageReductionModeFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Zero PhysicalDeviceCoverageReductionModeFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

data PipelineCoverageReductionStateCreateInfoNV Source #

VkPipelineCoverageReductionStateCreateInfoNV - Structure specifying parameters controlling coverage reduction

Description

If this structure is not included in the pNext chain, or if the extension is not enabled, the default coverage reduction mode is inferred as follows:

  • If the VK_NV_framebuffer_mixed_samples extension is enabled, then it is as if the coverageReductionMode is COVERAGE_REDUCTION_MODE_MERGE_NV.
  • If the VK_AMD_mixed_attachment_samples extension is enabled, then it is as if the coverageReductionMode is COVERAGE_REDUCTION_MODE_TRUNCATE_NV.
  • If both VK_NV_framebuffer_mixed_samples and VK_AMD_mixed_attachment_samples are enabled, then the default coverage reduction mode is implementation-dependent.

Valid Usage (Implicit)

See Also

VK_NV_coverage_reduction_mode, CoverageReductionModeNV, PipelineCoverageReductionStateCreateFlagsNV, StructureType

Constructors

PipelineCoverageReductionStateCreateInfoNV 

Fields

Instances

Instances details
Eq PipelineCoverageReductionStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Show PipelineCoverageReductionStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Storable PipelineCoverageReductionStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

FromCStruct PipelineCoverageReductionStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

ToCStruct PipelineCoverageReductionStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Zero PipelineCoverageReductionStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

data FramebufferMixedSamplesCombinationNV Source #

VkFramebufferMixedSamplesCombinationNV - Structure specifying a supported sample count combination

Valid Usage (Implicit)

See Also

VK_NV_coverage_reduction_mode, CoverageReductionModeNV, SampleCountFlagBits, SampleCountFlags, StructureType, getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV

Constructors

FramebufferMixedSamplesCombinationNV 

Fields

Instances

Instances details
Eq FramebufferMixedSamplesCombinationNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Show FramebufferMixedSamplesCombinationNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Storable FramebufferMixedSamplesCombinationNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

FromCStruct FramebufferMixedSamplesCombinationNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

ToCStruct FramebufferMixedSamplesCombinationNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Zero FramebufferMixedSamplesCombinationNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

newtype PipelineCoverageReductionStateCreateFlagsNV Source #

VkPipelineCoverageReductionStateCreateFlagsNV - Reserved for future use

Description

PipelineCoverageReductionStateCreateFlagsNV is a bitmask type for setting a mask, but is currently reserved for future use.

See Also

VK_NV_coverage_reduction_mode, PipelineCoverageReductionStateCreateInfoNV

Instances

Instances details
Eq PipelineCoverageReductionStateCreateFlagsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Ord PipelineCoverageReductionStateCreateFlagsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Read PipelineCoverageReductionStateCreateFlagsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Show PipelineCoverageReductionStateCreateFlagsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Storable PipelineCoverageReductionStateCreateFlagsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Bits PipelineCoverageReductionStateCreateFlagsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Methods

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

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

xor :: PipelineCoverageReductionStateCreateFlagsNV -> PipelineCoverageReductionStateCreateFlagsNV -> PipelineCoverageReductionStateCreateFlagsNV #

complement :: PipelineCoverageReductionStateCreateFlagsNV -> PipelineCoverageReductionStateCreateFlagsNV #

shift :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

rotate :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

zeroBits :: PipelineCoverageReductionStateCreateFlagsNV #

bit :: Int -> PipelineCoverageReductionStateCreateFlagsNV #

setBit :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

clearBit :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

complementBit :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

testBit :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> Bool #

bitSizeMaybe :: PipelineCoverageReductionStateCreateFlagsNV -> Maybe Int #

bitSize :: PipelineCoverageReductionStateCreateFlagsNV -> Int #

isSigned :: PipelineCoverageReductionStateCreateFlagsNV -> Bool #

shiftL :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

unsafeShiftL :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

shiftR :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

unsafeShiftR :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

rotateL :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

rotateR :: PipelineCoverageReductionStateCreateFlagsNV -> Int -> PipelineCoverageReductionStateCreateFlagsNV #

popCount :: PipelineCoverageReductionStateCreateFlagsNV -> Int #

FiniteBits PipelineCoverageReductionStateCreateFlagsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Zero PipelineCoverageReductionStateCreateFlagsNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

newtype CoverageReductionModeNV Source #

VkCoverageReductionModeNV - Specify the coverage reduction mode

See Also

VK_NV_coverage_reduction_mode, FramebufferMixedSamplesCombinationNV, PipelineCoverageReductionStateCreateInfoNV

Bundled Patterns

pattern COVERAGE_REDUCTION_MODE_MERGE_NV :: CoverageReductionModeNV

COVERAGE_REDUCTION_MODE_MERGE_NV specifies that each color sample will be associated with an implementation-dependent subset of samples in the pixel coverage. If any of those associated samples are covered, the color sample is covered.

pattern COVERAGE_REDUCTION_MODE_TRUNCATE_NV :: CoverageReductionModeNV

COVERAGE_REDUCTION_MODE_TRUNCATE_NV specifies that for color samples present in the color attachments, a color sample is covered if the pixel coverage sample with the same sample index i is covered; other pixel coverage samples are discarded.

Instances

Instances details
Eq CoverageReductionModeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Ord CoverageReductionModeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Read CoverageReductionModeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Show CoverageReductionModeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Storable CoverageReductionModeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

Zero CoverageReductionModeNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

type NV_COVERAGE_REDUCTION_MODE_EXTENSION_NAME = "VK_NV_coverage_reduction_mode" Source #