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

Vulkan.Extensions.VK_EXT_sample_locations

Synopsis

Documentation

cmdSetSampleLocationsEXT Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

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

-> SampleLocationsInfoEXT

pSampleLocationsInfo is the sample locations state to set.

-> io () 

vkCmdSetSampleLocationsEXT - Set the dynamic sample locations state

Valid Usage

  • The sampleLocationsPerPixel member of pSampleLocationsInfo must equal the rasterizationSamples member of the PipelineMultisampleStateCreateInfo structure the bound graphics pipeline has been created with
  • If PhysicalDeviceSampleLocationsPropertiesEXT::variableSampleLocations is FALSE then the current render pass must have been begun by specifying a RenderPassSampleLocationsBeginInfoEXT structure whose pPostSubpassSampleLocations member contains an element with a subpassIndex matching the current subpass index and the sampleLocationsInfo member of that element must match the sample locations state pointed to by pSampleLocationsInfo

Valid Usage (Implicit)

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 Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Both Graphics

See Also

CommandBuffer, SampleLocationsInfoEXT

getPhysicalDeviceMultisamplePropertiesEXT Source #

Arguments

:: forall io. MonadIO io 
=> PhysicalDevice

physicalDevice is the physical device from which to query the additional multisampling capabilities.

physicalDevice must be a valid PhysicalDevice handle

-> ("samples" ::: SampleCountFlagBits)

samples is the sample count to query the capabilities for.

samples must be a valid SampleCountFlagBits value

-> io MultisamplePropertiesEXT 

vkGetPhysicalDeviceMultisamplePropertiesEXT - Report sample count specific multisampling capabilities of a physical device

Valid Usage (Implicit)

See Also

MultisamplePropertiesEXT, PhysicalDevice, SampleCountFlagBits

data SampleLocationEXT Source #

VkSampleLocationEXT - Structure specifying the coordinates of a sample location

Description

The domain space of the sample location coordinates has an upper-left origin within the pixel in framebuffer space.

The values specified in a SampleLocationEXT structure are always clamped to the implementation-dependent sample location coordinate range [sampleLocationCoordinateRange[0],sampleLocationCoordinateRange[1]] that can be queried by adding a PhysicalDeviceSampleLocationsPropertiesEXT structure to the pNext chain of PhysicalDeviceProperties2.

See Also

SampleLocationsInfoEXT

Constructors

SampleLocationEXT 

Fields

  • x :: Float

    x is the horizontal coordinate of the sample’s location.

  • y :: Float

    y is the vertical coordinate of the sample’s location.

Instances

Instances details
Eq SampleLocationEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Show SampleLocationEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Generic SampleLocationEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Associated Types

type Rep SampleLocationEXT :: Type -> Type #

Storable SampleLocationEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

FromCStruct SampleLocationEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

ToCStruct SampleLocationEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Zero SampleLocationEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep SampleLocationEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep SampleLocationEXT = D1 ('MetaData "SampleLocationEXT" "Vulkan.Extensions.VK_EXT_sample_locations" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "SampleLocationEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "x") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float) :*: S1 ('MetaSel ('Just "y") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float)))

data SampleLocationsInfoEXT Source #

VkSampleLocationsInfoEXT - Structure specifying a set of sample locations

Description

This structure can be used either to specify the sample locations to be used for rendering or to specify the set of sample locations an image subresource has been last rendered with for the purposes of layout transitions of depth/stencil images created with IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT.

The sample locations in pSampleLocations specify sampleLocationsPerPixel number of sample locations for each pixel in the grid of the size specified in sampleLocationGridSize. The sample location for sample i at the pixel grid location (x,y) is taken from pSampleLocations[(x + y * sampleLocationGridSize.width) * sampleLocationsPerPixel + i].

If the render pass has a fragment density map, the implementation will choose the sample locations for the fragment and the contents of pSampleLocations may be ignored.

Valid Usage

  • sampleLocationsCount must equal sampleLocationsPerPixel × sampleLocationGridSize.width × sampleLocationGridSize.height

Valid Usage (Implicit)

  • If sampleLocationsPerPixel is not 0, sampleLocationsPerPixel must be a valid SampleCountFlagBits value
  • If sampleLocationsCount is not 0, pSampleLocations must be a valid pointer to an array of sampleLocationsCount SampleLocationEXT structures

See Also

AttachmentSampleLocationsEXT, Extent2D, PipelineSampleLocationsStateCreateInfoEXT, SampleCountFlagBits, SampleLocationEXT, StructureType, SubpassSampleLocationsEXT, cmdSetSampleLocationsEXT

Constructors

SampleLocationsInfoEXT 

Fields

Instances

Instances details
Show SampleLocationsInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Generic SampleLocationsInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Associated Types

type Rep SampleLocationsInfoEXT :: Type -> Type #

FromCStruct SampleLocationsInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

ToCStruct SampleLocationsInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Zero SampleLocationsInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep SampleLocationsInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep SampleLocationsInfoEXT = D1 ('MetaData "SampleLocationsInfoEXT" "Vulkan.Extensions.VK_EXT_sample_locations" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "SampleLocationsInfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "sampleLocationsPerPixel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SampleCountFlagBits) :*: (S1 ('MetaSel ('Just "sampleLocationGridSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Extent2D) :*: S1 ('MetaSel ('Just "sampleLocations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector SampleLocationEXT)))))

data AttachmentSampleLocationsEXT Source #

VkAttachmentSampleLocationsEXT - Structure specifying the sample locations state to use in the initial layout transition of attachments

Description

If the image referenced by the framebuffer attachment at index attachmentIndex was not created with IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT then the values specified in sampleLocationsInfo are ignored.

Valid Usage (Implicit)

See Also

RenderPassSampleLocationsBeginInfoEXT, SampleLocationsInfoEXT

Constructors

AttachmentSampleLocationsEXT 

Fields

  • attachmentIndex :: Word32

    attachmentIndex is the index of the attachment for which the sample locations state is provided.

    attachmentIndex must be less than the attachmentCount specified in RenderPassCreateInfo the render pass specified by RenderPassBeginInfo::renderPass was created with

  • sampleLocationsInfo :: SampleLocationsInfoEXT

    sampleLocationsInfo is the sample locations state to use for the layout transition of the given attachment from the initial layout of the attachment to the image layout specified for the attachment in the first subpass using it.

    sampleLocationsInfo must be a valid SampleLocationsInfoEXT structure

Instances

Instances details
Show AttachmentSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Generic AttachmentSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Associated Types

type Rep AttachmentSampleLocationsEXT :: Type -> Type #

FromCStruct AttachmentSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

ToCStruct AttachmentSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Zero AttachmentSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep AttachmentSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep AttachmentSampleLocationsEXT = D1 ('MetaData "AttachmentSampleLocationsEXT" "Vulkan.Extensions.VK_EXT_sample_locations" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "AttachmentSampleLocationsEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "attachmentIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "sampleLocationsInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SampleLocationsInfoEXT)))

data SubpassSampleLocationsEXT Source #

VkSubpassSampleLocationsEXT - Structure specifying the sample locations state to use for layout transitions of attachments performed after a given subpass

Description

If the image referenced by the depth/stencil attachment used in the subpass identified by subpassIndex was not created with IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT or if the subpass does not use a depth/stencil attachment, and PhysicalDeviceSampleLocationsPropertiesEXT::variableSampleLocations is TRUE then the values specified in sampleLocationsInfo are ignored.

Valid Usage (Implicit)

See Also

RenderPassSampleLocationsBeginInfoEXT, SampleLocationsInfoEXT

Constructors

SubpassSampleLocationsEXT 

Fields

Instances

Instances details
Show SubpassSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Generic SubpassSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Associated Types

type Rep SubpassSampleLocationsEXT :: Type -> Type #

FromCStruct SubpassSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

ToCStruct SubpassSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Zero SubpassSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep SubpassSampleLocationsEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep SubpassSampleLocationsEXT = D1 ('MetaData "SubpassSampleLocationsEXT" "Vulkan.Extensions.VK_EXT_sample_locations" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "SubpassSampleLocationsEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "subpassIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "sampleLocationsInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SampleLocationsInfoEXT)))

data RenderPassSampleLocationsBeginInfoEXT Source #

VkRenderPassSampleLocationsBeginInfoEXT - Structure specifying sample locations to use for the layout transition of custom sample locations compatible depth/stencil attachments

Valid Usage (Implicit)

  • If attachmentInitialSampleLocationsCount is not 0, pAttachmentInitialSampleLocations must be a valid pointer to an array of attachmentInitialSampleLocationsCount valid AttachmentSampleLocationsEXT structures
  • If postSubpassSampleLocationsCount is not 0, pPostSubpassSampleLocations must be a valid pointer to an array of postSubpassSampleLocationsCount valid SubpassSampleLocationsEXT structures

See Also

AttachmentSampleLocationsEXT, StructureType, SubpassSampleLocationsEXT

Constructors

RenderPassSampleLocationsBeginInfoEXT 

Fields

  • attachmentInitialSampleLocations :: Vector AttachmentSampleLocationsEXT

    pAttachmentInitialSampleLocations is a pointer to an array of attachmentInitialSampleLocationsCount AttachmentSampleLocationsEXT structures specifying the attachment indices and their corresponding sample location state. Each element of pAttachmentInitialSampleLocations can specify the sample location state to use in the automatic layout transition performed to transition a depth/stencil attachment from the initial layout of the attachment to the image layout specified for the attachment in the first subpass using it.

  • postSubpassSampleLocations :: Vector SubpassSampleLocationsEXT

    pPostSubpassSampleLocations is a pointer to an array of postSubpassSampleLocationsCount SubpassSampleLocationsEXT structures specifying the subpass indices and their corresponding sample location state. Each element of pPostSubpassSampleLocations can specify the sample location state to use in the automatic layout transition performed to transition the depth/stencil attachment used by the specified subpass to the image layout specified in a dependent subpass or to the final layout of the attachment in case the specified subpass is the last subpass using that attachment. In addition, if PhysicalDeviceSampleLocationsPropertiesEXT::variableSampleLocations is FALSE, each element of pPostSubpassSampleLocations must specify the sample location state that matches the sample locations used by all pipelines that will be bound to a command buffer during the specified subpass. If variableSampleLocations is TRUE, the sample locations used for rasterization do not depend on pPostSubpassSampleLocations.

Instances

Instances details
Show RenderPassSampleLocationsBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Generic RenderPassSampleLocationsBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

FromCStruct RenderPassSampleLocationsBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

ToCStruct RenderPassSampleLocationsBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Zero RenderPassSampleLocationsBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep RenderPassSampleLocationsBeginInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep RenderPassSampleLocationsBeginInfoEXT = D1 ('MetaData "RenderPassSampleLocationsBeginInfoEXT" "Vulkan.Extensions.VK_EXT_sample_locations" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "RenderPassSampleLocationsBeginInfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "attachmentInitialSampleLocations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector AttachmentSampleLocationsEXT)) :*: S1 ('MetaSel ('Just "postSubpassSampleLocations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector SubpassSampleLocationsEXT))))

data PipelineSampleLocationsStateCreateInfoEXT Source #

VkPipelineSampleLocationsStateCreateInfoEXT - Structure specifying sample locations for a pipeline

Valid Usage (Implicit)

See Also

Bool32, SampleLocationsInfoEXT, StructureType

Constructors

PipelineSampleLocationsStateCreateInfoEXT 

Fields

Instances

Instances details
Show PipelineSampleLocationsStateCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Generic PipelineSampleLocationsStateCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

FromCStruct PipelineSampleLocationsStateCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

ToCStruct PipelineSampleLocationsStateCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Zero PipelineSampleLocationsStateCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep PipelineSampleLocationsStateCreateInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep PipelineSampleLocationsStateCreateInfoEXT = D1 ('MetaData "PipelineSampleLocationsStateCreateInfoEXT" "Vulkan.Extensions.VK_EXT_sample_locations" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "PipelineSampleLocationsStateCreateInfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "sampleLocationsEnable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "sampleLocationsInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SampleLocationsInfoEXT)))

data PhysicalDeviceSampleLocationsPropertiesEXT Source #

VkPhysicalDeviceSampleLocationsPropertiesEXT - Structure describing sample location limits that can be supported by an implementation

Members

The members of the PhysicalDeviceSampleLocationsPropertiesEXT structure describe the following implementation-dependent limits:

Description

If the PhysicalDeviceSampleLocationsPropertiesEXT structure is included in the pNext chain of PhysicalDeviceProperties2, it is filled with the implementation-dependent limits.

Valid Usage (Implicit)

See Also

Bool32, Extent2D, SampleCountFlags, StructureType

Constructors

PhysicalDeviceSampleLocationsPropertiesEXT 

Fields

Instances

Instances details
Show PhysicalDeviceSampleLocationsPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Generic PhysicalDeviceSampleLocationsPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

FromCStruct PhysicalDeviceSampleLocationsPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

ToCStruct PhysicalDeviceSampleLocationsPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Zero PhysicalDeviceSampleLocationsPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep PhysicalDeviceSampleLocationsPropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep PhysicalDeviceSampleLocationsPropertiesEXT = D1 ('MetaData "PhysicalDeviceSampleLocationsPropertiesEXT" "Vulkan.Extensions.VK_EXT_sample_locations" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "PhysicalDeviceSampleLocationsPropertiesEXT" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sampleLocationSampleCounts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SampleCountFlags) :*: S1 ('MetaSel ('Just "maxSampleLocationGridSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Extent2D)) :*: (S1 ('MetaSel ('Just "sampleLocationCoordinateRange") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Float, Float)) :*: (S1 ('MetaSel ('Just "sampleLocationSubPixelBits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "variableSampleLocations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))))

data MultisamplePropertiesEXT Source #

VkMultisamplePropertiesEXT - Structure returning information about sample count specific additional multisampling capabilities

Valid Usage (Implicit)

See Also

Extent2D, StructureType, getPhysicalDeviceMultisamplePropertiesEXT

Constructors

MultisamplePropertiesEXT 

Fields

Instances

Instances details
Show MultisamplePropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Generic MultisamplePropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Associated Types

type Rep MultisamplePropertiesEXT :: Type -> Type #

FromCStruct MultisamplePropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

ToCStruct MultisamplePropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

Zero MultisamplePropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep MultisamplePropertiesEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_sample_locations

type Rep MultisamplePropertiesEXT = D1 ('MetaData "MultisamplePropertiesEXT" "Vulkan.Extensions.VK_EXT_sample_locations" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "MultisamplePropertiesEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "maxSampleLocationGridSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Extent2D)))

type EXT_SAMPLE_LOCATIONS_EXTENSION_NAME = "VK_EXT_sample_locations" Source #

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