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

Vulkan.Extensions.VK_NV_clip_space_w_scaling

Synopsis

Documentation

cmdSetViewportWScalingNV Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

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

-> ("firstViewport" ::: Word32)

firstViewport is the index of the first viewport whose parameters are updated by the command.

-> ("viewportWScalings" ::: Vector ViewportWScalingNV)

pViewportWScalings is a pointer to an array of ViewportWScalingNV structures specifying viewport parameters.

-> io () 

vkCmdSetViewportWScalingNV - Set the viewport W scaling on a command buffer

Description

The viewport parameters taken from element i of pViewportWScalings replace the current state for the viewport index firstViewport + i, for i in [0, viewportCount).

Valid Usage

  • The sum of firstViewport and viewportCount must be between 1 and PhysicalDeviceLimits::maxViewports, inclusive

Valid Usage (Implicit)

  • pViewportWScalings must be a valid pointer to an array of viewportCount ViewportWScalingNV structures
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics operations
  • viewportCount 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 Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Secondary Both Graphics

See Also

CommandBuffer, ViewportWScalingNV

data ViewportWScalingNV Source #

VkViewportWScalingNV - Structure specifying a viewport

See Also

PipelineViewportWScalingStateCreateInfoNV, cmdSetViewportWScalingNV

Constructors

ViewportWScalingNV 

Fields

  • xcoeff :: Float

    xcoeff and ycoeff are the viewport’s W scaling factor for x and y respectively.

  • ycoeff :: Float
     

Instances

Instances details
Eq ViewportWScalingNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

Show ViewportWScalingNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

Generic ViewportWScalingNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

Associated Types

type Rep ViewportWScalingNV :: Type -> Type #

Storable ViewportWScalingNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

FromCStruct ViewportWScalingNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

ToCStruct ViewportWScalingNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

Zero ViewportWScalingNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

type Rep ViewportWScalingNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

type Rep ViewportWScalingNV = D1 ('MetaData "ViewportWScalingNV" "Vulkan.Extensions.VK_NV_clip_space_w_scaling" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "ViewportWScalingNV" 'PrefixI 'True) (S1 ('MetaSel ('Just "xcoeff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float) :*: S1 ('MetaSel ('Just "ycoeff") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float)))

data PipelineViewportWScalingStateCreateInfoNV Source #

VkPipelineViewportWScalingStateCreateInfoNV - Structure specifying parameters of a newly created pipeline viewport W scaling state

Valid Usage (Implicit)

See Also

Bool32, StructureType, ViewportWScalingNV

Constructors

PipelineViewportWScalingStateCreateInfoNV 

Fields

  • viewportWScalingEnable :: Bool

    viewportWScalingEnable controls whether viewport W scaling is enabled.

  • viewportCount :: Word32

    viewportCount is the number of viewports used by W scaling, and must match the number of viewports in the pipeline if viewport W scaling is enabled.

    viewportCount must be greater than 0

  • viewportWScalings :: Vector ViewportWScalingNV

    pViewportWScalings is a pointer to an array of ViewportWScalingNV structures defining the W scaling parameters for the corresponding viewports. If the viewport W scaling state is dynamic, this member is ignored.

Instances

Instances details
Show PipelineViewportWScalingStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

Generic PipelineViewportWScalingStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

FromCStruct PipelineViewportWScalingStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

ToCStruct PipelineViewportWScalingStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

Zero PipelineViewportWScalingStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

type Rep PipelineViewportWScalingStateCreateInfoNV Source # 
Instance details

Defined in Vulkan.Extensions.VK_NV_clip_space_w_scaling

type Rep PipelineViewportWScalingStateCreateInfoNV = D1 ('MetaData "PipelineViewportWScalingStateCreateInfoNV" "Vulkan.Extensions.VK_NV_clip_space_w_scaling" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "PipelineViewportWScalingStateCreateInfoNV" 'PrefixI 'True) (S1 ('MetaSel ('Just "viewportWScalingEnable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "viewportCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "viewportWScalings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector ViewportWScalingNV)))))

type NV_CLIP_SPACE_W_SCALING_EXTENSION_NAME = "VK_NV_clip_space_w_scaling" Source #

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