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

Vulkan.Extensions.VK_NV_coverage_reduction_mode

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 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

FramebufferMixedSamplesCombinationNV, PhysicalDevice

data PhysicalDeviceCoverageReductionModeFeaturesNV Source #

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

Members

The members of the PhysicalDeviceCoverageReductionModeFeaturesNV structure describe the following features:

Description

If the PhysicalDeviceCoverageReductionModeFeaturesNV structure is included in the pNext chain of PhysicalDeviceFeatures2, it is filled with values indicating whether the feature is supported. PhysicalDeviceCoverageReductionModeFeaturesNV can also be included in the pNext chain of DeviceCreateInfo to enable the feature.

Valid Usage (Implicit)

See Also

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

Generic 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

type Rep PhysicalDeviceCoverageReductionModeFeaturesNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

type Rep PhysicalDeviceCoverageReductionModeFeaturesNV = D1 ('MetaData "PhysicalDeviceCoverageReductionModeFeaturesNV" "Vulkan.Extensions.VK_NV_coverage_reduction_mode" "vulkan-3.4-inplace" 'False) (C1 ('MetaCons "PhysicalDeviceCoverageReductionModeFeaturesNV" 'PrefixI 'True) (S1 ('MetaSel ('Just "coverageReductionMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))

data PipelineCoverageReductionStateCreateInfoNV Source #

VkPipelineCoverageReductionStateCreateInfoNV - Structure specifying parameters controlling coverage reduction

Description

If this structure is not present, 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

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

Generic 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

type Rep PipelineCoverageReductionStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

type Rep PipelineCoverageReductionStateCreateInfoNV = D1 ('MetaData "PipelineCoverageReductionStateCreateInfoNV" "Vulkan.Extensions.VK_NV_coverage_reduction_mode" "vulkan-3.4-inplace" 'False) (C1 ('MetaCons "PipelineCoverageReductionStateCreateInfoNV" 'PrefixI 'True) (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PipelineCoverageReductionStateCreateFlagsNV) :*: S1 ('MetaSel ('Just "coverageReductionMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CoverageReductionModeNV)))

data FramebufferMixedSamplesCombinationNV Source #

VkFramebufferMixedSamplesCombinationNV - Structure specifying a supported sample count combination

Valid Usage (Implicit)

See Also

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

Generic 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

type Rep FramebufferMixedSamplesCombinationNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_coverage_reduction_mode

type Rep FramebufferMixedSamplesCombinationNV = D1 ('MetaData "FramebufferMixedSamplesCombinationNV" "Vulkan.Extensions.VK_NV_coverage_reduction_mode" "vulkan-3.4-inplace" 'False) (C1 ('MetaCons "FramebufferMixedSamplesCombinationNV" 'PrefixI 'True) ((S1 ('MetaSel ('Just "coverageReductionMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CoverageReductionModeNV) :*: S1 ('MetaSel ('Just "rasterizationSamples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SampleCountFlagBits)) :*: (S1 ('MetaSel ('Just "depthStencilSamples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SampleCountFlags) :*: S1 ('MetaSel ('Just "colorSamples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SampleCountFlags))))

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

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 #

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

FramebufferMixedSamplesCombinationNV, PipelineCoverageReductionStateCreateInfoNV

Bundled Patterns

pattern COVERAGE_REDUCTION_MODE_MERGE_NV :: CoverageReductionModeNV

COVERAGE_REDUCTION_MODE_MERGE_NV: In this mode, there is an implementation-dependent association of each coverage sample to a color sample. The reduced color sample mask is computed such that the bit for each color sample is 1 if any of the associated bits in the fragment’s coverage is on, and 0 otherwise.

pattern COVERAGE_REDUCTION_MODE_TRUNCATE_NV :: CoverageReductionModeNV

COVERAGE_REDUCTION_MODE_TRUNCATE_NV: In this mode, only the first M coverage samples are associated with the color samples such that sample index i maps to color sample index i, where M is the number of color samples.

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 #