vulkan-2.0.0.1: Bindings to the Vulkan graphics API.

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Core10.Pipeline

Synopsis

Documentation

newtype VkBlendFactor Source #

VkBlendFactor - Framebuffer blending factors

Description

The semantics of each enum value is described in the table below:

VkBlendFactor RGB Blend Factors (Sr,Sg,Sb) or (Dr,Dg,Db) Alpha Blend Factor (Sa or Da)
VK_BLEND_FACTOR_ZERO (0,0,0) 0
VK_BLEND_FACTOR_ONE (1,1,1) 1
VK_BLEND_FACTOR_SRC_COLOR (Rs0,Gs0,Bs0) As0
VK_BLEND_FACTOR_ONE_MINUS_SRC_COLOR (1-Rs0,1-Gs0,1-Bs0) 1-As0
VK_BLEND_FACTOR_DST_COLOR (Rd,Gd,Bd) Ad
VK_BLEND_FACTOR_ONE_MINUS_DST_COLOR (1-Rd,1-Gd,1-Bd) 1-Ad
VK_BLEND_FACTOR_SRC_ALPHA (As0,As0,As0) As0
VK_BLEND_FACTOR_ONE_MINUS_SRC_ALPHA (1-As0,1-As0,1-As0) 1-As0
VK_BLEND_FACTOR_DST_ALPHA (Ad,Ad,Ad) Ad
VK_BLEND_FACTOR_ONE_MINUS_DST_ALPHA (1-Ad,1-Ad,1-Ad) 1-Ad
VK_BLEND_FACTOR_CONSTANT_COLOR (Rc,Gc,Bc) Ac
VK_BLEND_FACTOR_ONE_MINUS_CONSTANT_COLOR (1-Rc,1-Gc,1-Bc) 1-Ac
VK_BLEND_FACTOR_CONSTANT_ALPHA (Ac,Ac,Ac) Ac
VK_BLEND_FACTOR_ONE_MINUS_CONSTANT_ALPHA (1-Ac,1-Ac,1-Ac) 1-Ac
VK_BLEND_FACTOR_SRC_ALPHA_SATURATE (f,f,f); f = min(As0,1-Ad) 1
VK_BLEND_FACTOR_SRC1_COLOR (Rs1,Gs1,Bs1) As1
VK_BLEND_FACTOR_ONE_MINUS_SRC1_COLOR (1-Rs1,1-Gs1,1-Bs1) 1-As1
VK_BLEND_FACTOR_SRC1_ALPHA (As1,As1,As1) As1
VK_BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA (1-As1,1-As1,1-As1) 1-As1

Blend Factors

In this table, the following conventions are used:

  • Rs0,Gs0,Bs0 and As0 represent the first source color R, G, B, and A components, respectively, for the fragment output location corresponding to the color attachment being blended.
  • Rs1,Gs1,Bs1 and As1 represent the second source color R, G, B, and A components, respectively, used in dual source blending modes, for the fragment output location corresponding to the color attachment being blended.
  • Rd,Gd,Bd and Ad represent the R, G, B, and A components of the destination color. That is, the color currently in the corresponding color attachment for this fragment/sample.
  • Rc,Gc,Bc and Ac represent the blend constant R, G, B, and A components, respectively.

See Also

VkPipelineColorBlendAttachmentState

Constructors

VkBlendFactor Int32 

newtype VkBlendOp Source #

VkBlendOp - Framebuffer blending operations

Description

The semantics of each basic blend operations is described in the table below:

VkBlendOp RGB Components Alpha Component

| VK_BLEND_OP_ADD | R = Rs0 × Sr + Rd | A = As0 × Sa + | | | × Dr | Ad × Da | | | G = Gs0 × Sg + Gd | | | | × Dg | | | | B = Bs0 × Sb + Bd | | | | × Db | | +--------------------------------+--------------------+----------------+ | VK_BLEND_OP_SUBTRACT | R = Rs0 × Sr - Rd | A = As0 × Sa - | | | × Dr | Ad × Da | | | G = Gs0 × Sg - Gd | | | | × Dg | | | | B = Bs0 × Sb - Bd | | | | × Db | | +--------------------------------+--------------------+----------------+ | VK_BLEND_OP_REVERSE_SUBTRACT | R = Rd × Dr - Rs0 | A = Ad × Da - | | | × Sr | As0 × Sa | | | G = Gd × Dg - Gs0 | | | | × Sg | | | | B = Bd × Db - Bs0 | | | | × Sb | | +--------------------------------+--------------------+----------------+ | VK_BLEND_OP_MIN | R = min(Rs0,Rd) | A = | | | G = min(Gs0,Gd) | min(As0,Ad) | | | B = min(Bs0,Bd) | | +--------------------------------+--------------------+----------------+ | VK_BLEND_OP_MAX | R = max(Rs0,Rd) | A = | | | G = max(Gs0,Gd) | max(As0,Ad) | | | B = max(Bs0,Bd) | | +--------------------------------+--------------------+----------------+

Basic Blend Operations

In this table, the following conventions are used:

  • Rs0, Gs0, Bs0 and As0 represent the first source color R, G, B, and A components, respectively.
  • Rd, Gd, Bd and Ad represent the R, G, B, and A components of the destination color. That is, the color currently in the corresponding color attachment for this fragment/sample.
  • Sr, Sg, Sb and Sa represent the source blend factor R, G, B, and A components, respectively.
  • Dr, Dg, Db and Da represent the destination blend factor R, G, B, and A components, respectively.

The blending operation produces a new set of values R, G, B and A, which are written to the framebuffer attachment. If blending is not enabled for this attachment, then R, G, B and A are assigned Rs0, Gs0, Bs0 and As0, respectively.

If the color attachment is fixed-point, the components of the source and destination values and blend factors are each clamped to [0,1] or [-1,1] respectively for an unsigned normalized or signed normalized color attachment prior to evaluating the blend operations. If the color attachment is floating-point, no clamping occurs.

See Also

VkPipelineColorBlendAttachmentState

Constructors

VkBlendOp Int32 

pattern VK_COMPARE_OP_NEVER :: VkCompareOp Source #

VK_COMPARE_OP_NEVER specifies that the test never passes.

pattern VK_COMPARE_OP_LESS :: VkCompareOp Source #

VK_COMPARE_OP_LESS specifies that the test passes when R < S.

pattern VK_COMPARE_OP_EQUAL :: VkCompareOp Source #

VK_COMPARE_OP_EQUAL specifies that the test passes when R = S.

pattern VK_COMPARE_OP_LESS_OR_EQUAL :: VkCompareOp Source #

VK_COMPARE_OP_LESS_OR_EQUAL specifies that the test passes when R ≤ S.

pattern VK_COMPARE_OP_GREATER :: VkCompareOp Source #

VK_COMPARE_OP_GREATER specifies that the test passes when R > S.

pattern VK_COMPARE_OP_NOT_EQUAL :: VkCompareOp Source #

VK_COMPARE_OP_NOT_EQUAL specifies that the test passes when R ≠ S.

pattern VK_COMPARE_OP_GREATER_OR_EQUAL :: VkCompareOp Source #

VK_COMPARE_OP_GREATER_OR_EQUAL specifies that the test passes when R ≥ S.

pattern VK_COMPARE_OP_ALWAYS :: VkCompareOp Source #

VK_COMPARE_OP_ALWAYS specifies that the test always passes.

newtype VkDynamicState Source #

VkDynamicState - Indicate which dynamic state is taken from dynamic state commands

See Also

VkPipelineDynamicStateCreateInfo

Constructors

VkDynamicState Int32 

pattern VK_DYNAMIC_STATE_VIEWPORT :: VkDynamicState Source #

VK_DYNAMIC_STATE_VIEWPORT specifies that the pViewports state in VkPipelineViewportStateCreateInfo will be ignored and must be set dynamically with vkCmdSetViewport before any draw commands. The number of viewports used by a pipeline is still specified by the viewportCount member of VkPipelineViewportStateCreateInfo.

pattern VK_DYNAMIC_STATE_SCISSOR :: VkDynamicState Source #

VK_DYNAMIC_STATE_SCISSOR specifies that the pScissors state in VkPipelineViewportStateCreateInfo will be ignored and must be set dynamically with vkCmdSetScissor before any draw commands. The number of scissor rectangles used by a pipeline is still specified by the scissorCount member of VkPipelineViewportStateCreateInfo.

pattern VK_DYNAMIC_STATE_LINE_WIDTH :: VkDynamicState Source #

VK_DYNAMIC_STATE_LINE_WIDTH specifies that the lineWidth state in VkPipelineRasterizationStateCreateInfo will be ignored and must be set dynamically with vkCmdSetLineWidth before any draw commands that generate line primitives for the rasterizer.

pattern VK_DYNAMIC_STATE_DEPTH_BIAS :: VkDynamicState Source #

VK_DYNAMIC_STATE_DEPTH_BIAS specifies that the depthBiasConstantFactor, depthBiasClamp and depthBiasSlopeFactor states in VkPipelineRasterizationStateCreateInfo will be ignored and must be set dynamically with vkCmdSetDepthBias before any draws are performed with depthBiasEnable in VkPipelineRasterizationStateCreateInfo set to VK_TRUE.

pattern VK_DYNAMIC_STATE_BLEND_CONSTANTS :: VkDynamicState Source #

VK_DYNAMIC_STATE_BLEND_CONSTANTS specifies that the blendConstants state in VkPipelineColorBlendStateCreateInfo will be ignored and must be set dynamically with vkCmdSetBlendConstants before any draws are performed with a pipeline state with VkPipelineColorBlendAttachmentState member blendEnable set to VK_TRUE and any of the blend functions using a constant blend color.

pattern VK_DYNAMIC_STATE_DEPTH_BOUNDS :: VkDynamicState Source #

VK_DYNAMIC_STATE_DEPTH_BOUNDS specifies that the minDepthBounds and maxDepthBounds states of VkPipelineDepthStencilStateCreateInfo will be ignored and must be set dynamically with vkCmdSetDepthBounds before any draws are performed with a pipeline state with VkPipelineDepthStencilStateCreateInfo member depthBoundsTestEnable set to VK_TRUE.

pattern VK_DYNAMIC_STATE_STENCIL_COMPARE_MASK :: VkDynamicState Source #

VK_DYNAMIC_STATE_STENCIL_COMPARE_MASK specifies that the compareMask state in VkPipelineDepthStencilStateCreateInfo for both front and back will be ignored and must be set dynamically with vkCmdSetStencilCompareMask before any draws are performed with a pipeline state with VkPipelineDepthStencilStateCreateInfo member stencilTestEnable set to VK_TRUE

pattern VK_DYNAMIC_STATE_STENCIL_WRITE_MASK :: VkDynamicState Source #

VK_DYNAMIC_STATE_STENCIL_WRITE_MASK specifies that the writeMask state in VkPipelineDepthStencilStateCreateInfo for both front and back will be ignored and must be set dynamically with vkCmdSetStencilWriteMask before any draws are performed with a pipeline state with VkPipelineDepthStencilStateCreateInfo member stencilTestEnable set to VK_TRUE

pattern VK_DYNAMIC_STATE_STENCIL_REFERENCE :: VkDynamicState Source #

VK_DYNAMIC_STATE_STENCIL_REFERENCE specifies that the reference state in VkPipelineDepthStencilStateCreateInfo for both front and back will be ignored and must be set dynamically with vkCmdSetStencilReference before any draws are performed with a pipeline state with VkPipelineDepthStencilStateCreateInfo member stencilTestEnable set to VK_TRUE

newtype VkPolygonMode Source #

VkPolygonMode - Control polygon rasterization mode

Description

  • VK_POLYGON_MODE_POINT specifies that polygon vertices are drawn as points.
  • VK_POLYGON_MODE_LINE specifies that polygon edges are drawn as line segments.
  • VK_POLYGON_MODE_FILL specifies that polygons are rendered using the polygon rasterization rules in this section.
  • VK_POLYGON_MODE_FILL_RECTANGLE_NV specifies that polygons are rendered using polygon rasterization rules, modified to consider a sample within the primitive if the sample location is inside the axis-aligned bounding box of the triangle after projection. Note that the barycentric weights used in attribute interpolation can extend outside the range [0,1] when these primitives are shaded. Special treatment is given to a sample position on the boundary edge of the bounding box. In such a case, if two rectangles lie on either side of a common edge (with identical endpoints) on which a sample position lies, then exactly one of the triangles must produce a fragment that covers that sample during rasterization.

    Polygons rendered in VK_POLYGON_MODE_FILL_RECTANGLE_NV mode may be clipped by the frustum or by user clip planes. If clipping is applied, the triangle is culled rather than clipped.

    Area calculation and facingness are determined for VK_POLYGON_MODE_FILL_RECTANGLE_NV mode using the triangle’s vertices.

These modes affect only the final rasterization of polygons: in particular, a polygon’s vertices are shaded and the polygon is clipped and possibly culled before these modes are applied.

See Also

VkPipelineRasterizationStateCreateInfo

Constructors

VkPolygonMode Int32 

newtype VkFrontFace Source #

VkFrontFace - Interpret polygon front-facing orientation

Description

  • VK_FRONT_FACE_COUNTER_CLOCKWISE specifies that a triangle with positive area is considered front-facing.
  • VK_FRONT_FACE_CLOCKWISE specifies that a triangle with negative area is considered front-facing.

Any triangle which is not front-facing is back-facing, including zero-area triangles.

See Also

VkPipelineRasterizationStateCreateInfo

Constructors

VkFrontFace Int32 

newtype VkLogicOp Source #

VkLogicOp - Framebuffer logical operations

Description

The logical operations supported by Vulkan are summarized in the following table in which

  • ¬ is bitwise invert,
  • ∧ is bitwise and,
  • ∨ is bitwise or,
  • ⊕ is bitwise exclusive or,
  • s is the fragment’s Rs0, Gs0, Bs0 or As0 component value for the fragment output corresponding to the color attachment being updated, and
  • d is the color attachment’s R, G, B or A component value:
Mode Operation
VK_LOGIC_OP_CLEAR 0

| VK_LOGIC_OP_AND | s ∧ d | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_AND_REVERSE | s ∧ ¬ d | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_COPY | s | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_AND_INVERTED | ¬ s ∧ d | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_NO_OP | d | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_XOR | s ⊕ d | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_OR | s ∨ d | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_NOR | ¬ (s ∨ d) | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_EQUIVALENT | ¬ (s ⊕ d) | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_INVERT | ¬ d | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_OR_REVERSE | s ∨ ¬ d | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_COPY_INVERTED | ¬ s | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_OR_INVERTED | ¬ s ∨ d | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_NAND | ¬ (s ∧ d) | +-----------------------------------+-----------------------------------+ | VK_LOGIC_OP_SET | all 1s | +-----------------------------------+-----------------------------------+

Logical Operations

The result of the logical operation is then written to the color attachment as controlled by the component write mask, described in Blend Operations.

See Also

VkPipelineColorBlendStateCreateInfo

Constructors

VkLogicOp Int32 

newtype VkPrimitiveTopology Source #

VkPrimitiveTopology - Supported primitive topologies

See Also

VkPipelineInputAssemblyStateCreateInfo

Instances
Eq VkPrimitiveTopology Source # 
Instance details
Ord VkPrimitiveTopology Source # 
Instance details
Read VkPrimitiveTopology Source # 
Instance details
Show VkPrimitiveTopology Source # 
Instance details
Storable VkPrimitiveTopology Source # 
Instance details

newtype VkStencilOp Source #

VkStencilOp - Stencil comparison function

Description

  • VK_STENCIL_OP_KEEP keeps the current value.
  • VK_STENCIL_OP_ZERO sets the value to 0.
  • VK_STENCIL_OP_REPLACE sets the value to reference.
  • VK_STENCIL_OP_INCREMENT_AND_CLAMP increments the current value and clamps to the maximum representable unsigned value.
  • VK_STENCIL_OP_DECREMENT_AND_CLAMP decrements the current value and clamps to 0.
  • VK_STENCIL_OP_INVERT bitwise-inverts the current value.
  • VK_STENCIL_OP_INCREMENT_AND_WRAP increments the current value and wraps to 0 when the maximum value would have been exceeded.
  • VK_STENCIL_OP_DECREMENT_AND_WRAP decrements the current value and wraps to the maximum possible value when the value would go below 0.

For purposes of increment and decrement, the stencil bits are considered as an unsigned integer.

If the stencil test fails, the sample’s coverage bit is cleared in the fragment. If there is no stencil framebuffer attachment, stencil modification cannot occur, and it is as if the stencil tests always pass.

If the stencil test passes, the writeMask member of the VkStencilOpState structures controls how the updated stencil value is written to the stencil framebuffer attachment.

The least significant s bits of writeMask, where s is the number of bits in the stencil framebuffer attachment, specify an integer mask. Where a 1 appears in this mask, the corresponding bit in the stencil value in the depth/stencil attachment is written; where a 0 appears, the bit is not written. The writeMask value uses either the front-facing or back-facing state based on the facingness of the fragment. Fragments generated by front-facing primitives use the front mask and fragments generated by back-facing primitives use the back mask.

See Also

VkStencilOpState

Constructors

VkStencilOp Int32 

newtype VkVertexInputRate Source #

VkVertexInputRate - Specify rate at which vertex attributes are pulled from buffers

See Also

VkVertexInputBindingDescription

Constructors

VkVertexInputRate Int32 
Instances
Eq VkVertexInputRate Source # 
Instance details
Ord VkVertexInputRate Source # 
Instance details
Read VkVertexInputRate Source # 
Instance details
Show VkVertexInputRate Source # 
Instance details
Storable VkVertexInputRate Source # 
Instance details

pattern VK_VERTEX_INPUT_RATE_VERTEX :: VkVertexInputRate Source #

VK_VERTEX_INPUT_RATE_VERTEX specifies that vertex attribute addressing is a function of the vertex index.

pattern VK_VERTEX_INPUT_RATE_INSTANCE :: VkVertexInputRate Source #

VK_VERTEX_INPUT_RATE_INSTANCE specifies that vertex attribute addressing is a function of the instance index.

newtype VkPipelineDepthStencilStateCreateFlags Source #

VkPipelineDepthStencilStateCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineDepthStencilStateCreateInfo

Instances
Eq VkPipelineDepthStencilStateCreateFlags Source # 
Instance details
Ord VkPipelineDepthStencilStateCreateFlags Source # 
Instance details
Read VkPipelineDepthStencilStateCreateFlags Source # 
Instance details
Show VkPipelineDepthStencilStateCreateFlags Source # 
Instance details
Storable VkPipelineDepthStencilStateCreateFlags Source # 
Instance details
Bits VkPipelineDepthStencilStateCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineDepthStencilStateCreateFlags -> VkPipelineDepthStencilStateCreateFlags -> VkPipelineDepthStencilStateCreateFlags #

complement :: VkPipelineDepthStencilStateCreateFlags -> VkPipelineDepthStencilStateCreateFlags #

shift :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

rotate :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

zeroBits :: VkPipelineDepthStencilStateCreateFlags #

bit :: Int -> VkPipelineDepthStencilStateCreateFlags #

setBit :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

clearBit :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

complementBit :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

testBit :: VkPipelineDepthStencilStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineDepthStencilStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineDepthStencilStateCreateFlags -> Int #

isSigned :: VkPipelineDepthStencilStateCreateFlags -> Bool #

shiftL :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

unsafeShiftL :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

shiftR :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

unsafeShiftR :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

rotateL :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

rotateR :: VkPipelineDepthStencilStateCreateFlags -> Int -> VkPipelineDepthStencilStateCreateFlags #

popCount :: VkPipelineDepthStencilStateCreateFlags -> Int #

FiniteBits VkPipelineDepthStencilStateCreateFlags Source # 
Instance details

newtype VkPipelineDynamicStateCreateFlags Source #

VkPipelineDynamicStateCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineDynamicStateCreateInfo

Instances
Eq VkPipelineDynamicStateCreateFlags Source # 
Instance details
Ord VkPipelineDynamicStateCreateFlags Source # 
Instance details
Read VkPipelineDynamicStateCreateFlags Source # 
Instance details
Show VkPipelineDynamicStateCreateFlags Source # 
Instance details
Storable VkPipelineDynamicStateCreateFlags Source # 
Instance details
Bits VkPipelineDynamicStateCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineDynamicStateCreateFlags -> VkPipelineDynamicStateCreateFlags -> VkPipelineDynamicStateCreateFlags #

complement :: VkPipelineDynamicStateCreateFlags -> VkPipelineDynamicStateCreateFlags #

shift :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

rotate :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

zeroBits :: VkPipelineDynamicStateCreateFlags #

bit :: Int -> VkPipelineDynamicStateCreateFlags #

setBit :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

clearBit :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

complementBit :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

testBit :: VkPipelineDynamicStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineDynamicStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineDynamicStateCreateFlags -> Int #

isSigned :: VkPipelineDynamicStateCreateFlags -> Bool #

shiftL :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

unsafeShiftL :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

shiftR :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

unsafeShiftR :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

rotateL :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

rotateR :: VkPipelineDynamicStateCreateFlags -> Int -> VkPipelineDynamicStateCreateFlags #

popCount :: VkPipelineDynamicStateCreateFlags -> Int #

FiniteBits VkPipelineDynamicStateCreateFlags Source # 
Instance details

newtype VkPipelineColorBlendStateCreateFlags Source #

VkPipelineColorBlendStateCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineColorBlendStateCreateInfo

Instances
Eq VkPipelineColorBlendStateCreateFlags Source # 
Instance details
Ord VkPipelineColorBlendStateCreateFlags Source # 
Instance details
Read VkPipelineColorBlendStateCreateFlags Source # 
Instance details
Show VkPipelineColorBlendStateCreateFlags Source # 
Instance details
Storable VkPipelineColorBlendStateCreateFlags Source # 
Instance details
Bits VkPipelineColorBlendStateCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineColorBlendStateCreateFlags -> VkPipelineColorBlendStateCreateFlags -> VkPipelineColorBlendStateCreateFlags #

complement :: VkPipelineColorBlendStateCreateFlags -> VkPipelineColorBlendStateCreateFlags #

shift :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

rotate :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

zeroBits :: VkPipelineColorBlendStateCreateFlags #

bit :: Int -> VkPipelineColorBlendStateCreateFlags #

setBit :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

clearBit :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

complementBit :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

testBit :: VkPipelineColorBlendStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineColorBlendStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineColorBlendStateCreateFlags -> Int #

isSigned :: VkPipelineColorBlendStateCreateFlags -> Bool #

shiftL :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

unsafeShiftL :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

shiftR :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

unsafeShiftR :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

rotateL :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

rotateR :: VkPipelineColorBlendStateCreateFlags -> Int -> VkPipelineColorBlendStateCreateFlags #

popCount :: VkPipelineColorBlendStateCreateFlags -> Int #

FiniteBits VkPipelineColorBlendStateCreateFlags Source # 
Instance details

newtype VkPipelineMultisampleStateCreateFlags Source #

VkPipelineMultisampleStateCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineMultisampleStateCreateInfo

Instances
Eq VkPipelineMultisampleStateCreateFlags Source # 
Instance details
Ord VkPipelineMultisampleStateCreateFlags Source # 
Instance details
Read VkPipelineMultisampleStateCreateFlags Source # 
Instance details
Show VkPipelineMultisampleStateCreateFlags Source # 
Instance details
Storable VkPipelineMultisampleStateCreateFlags Source # 
Instance details
Bits VkPipelineMultisampleStateCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineMultisampleStateCreateFlags -> VkPipelineMultisampleStateCreateFlags -> VkPipelineMultisampleStateCreateFlags #

complement :: VkPipelineMultisampleStateCreateFlags -> VkPipelineMultisampleStateCreateFlags #

shift :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

rotate :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

zeroBits :: VkPipelineMultisampleStateCreateFlags #

bit :: Int -> VkPipelineMultisampleStateCreateFlags #

setBit :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

clearBit :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

complementBit :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

testBit :: VkPipelineMultisampleStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineMultisampleStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineMultisampleStateCreateFlags -> Int #

isSigned :: VkPipelineMultisampleStateCreateFlags -> Bool #

shiftL :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

unsafeShiftL :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

shiftR :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

unsafeShiftR :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

rotateL :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

rotateR :: VkPipelineMultisampleStateCreateFlags -> Int -> VkPipelineMultisampleStateCreateFlags #

popCount :: VkPipelineMultisampleStateCreateFlags -> Int #

FiniteBits VkPipelineMultisampleStateCreateFlags Source # 
Instance details

newtype VkPipelineRasterizationStateCreateFlags Source #

VkPipelineRasterizationStateCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineRasterizationStateCreateInfo

Instances
Eq VkPipelineRasterizationStateCreateFlags Source # 
Instance details
Ord VkPipelineRasterizationStateCreateFlags Source # 
Instance details
Read VkPipelineRasterizationStateCreateFlags Source # 
Instance details
Show VkPipelineRasterizationStateCreateFlags Source # 
Instance details
Storable VkPipelineRasterizationStateCreateFlags Source # 
Instance details
Bits VkPipelineRasterizationStateCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags #

complement :: VkPipelineRasterizationStateCreateFlags -> VkPipelineRasterizationStateCreateFlags #

shift :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

rotate :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

zeroBits :: VkPipelineRasterizationStateCreateFlags #

bit :: Int -> VkPipelineRasterizationStateCreateFlags #

setBit :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

clearBit :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

complementBit :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

testBit :: VkPipelineRasterizationStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineRasterizationStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineRasterizationStateCreateFlags -> Int #

isSigned :: VkPipelineRasterizationStateCreateFlags -> Bool #

shiftL :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

unsafeShiftL :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

shiftR :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

unsafeShiftR :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

rotateL :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

rotateR :: VkPipelineRasterizationStateCreateFlags -> Int -> VkPipelineRasterizationStateCreateFlags #

popCount :: VkPipelineRasterizationStateCreateFlags -> Int #

FiniteBits VkPipelineRasterizationStateCreateFlags Source # 
Instance details

newtype VkPipelineViewportStateCreateFlags Source #

VkPipelineViewportStateCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineViewportStateCreateInfo

Instances
Eq VkPipelineViewportStateCreateFlags Source # 
Instance details
Ord VkPipelineViewportStateCreateFlags Source # 
Instance details
Read VkPipelineViewportStateCreateFlags Source # 
Instance details
Show VkPipelineViewportStateCreateFlags Source # 
Instance details
Storable VkPipelineViewportStateCreateFlags Source # 
Instance details
Bits VkPipelineViewportStateCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags #

complement :: VkPipelineViewportStateCreateFlags -> VkPipelineViewportStateCreateFlags #

shift :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

rotate :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

zeroBits :: VkPipelineViewportStateCreateFlags #

bit :: Int -> VkPipelineViewportStateCreateFlags #

setBit :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

clearBit :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

complementBit :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

testBit :: VkPipelineViewportStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineViewportStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineViewportStateCreateFlags -> Int #

isSigned :: VkPipelineViewportStateCreateFlags -> Bool #

shiftL :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

unsafeShiftL :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

shiftR :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

unsafeShiftR :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

rotateL :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

rotateR :: VkPipelineViewportStateCreateFlags -> Int -> VkPipelineViewportStateCreateFlags #

popCount :: VkPipelineViewportStateCreateFlags -> Int #

FiniteBits VkPipelineViewportStateCreateFlags Source # 
Instance details

newtype VkPipelineTessellationStateCreateFlags Source #

VkPipelineTessellationStateCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineTessellationStateCreateInfo

Instances
Eq VkPipelineTessellationStateCreateFlags Source # 
Instance details
Ord VkPipelineTessellationStateCreateFlags Source # 
Instance details
Read VkPipelineTessellationStateCreateFlags Source # 
Instance details
Show VkPipelineTessellationStateCreateFlags Source # 
Instance details
Storable VkPipelineTessellationStateCreateFlags Source # 
Instance details
Bits VkPipelineTessellationStateCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags #

complement :: VkPipelineTessellationStateCreateFlags -> VkPipelineTessellationStateCreateFlags #

shift :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

rotate :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

zeroBits :: VkPipelineTessellationStateCreateFlags #

bit :: Int -> VkPipelineTessellationStateCreateFlags #

setBit :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

clearBit :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

complementBit :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

testBit :: VkPipelineTessellationStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineTessellationStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineTessellationStateCreateFlags -> Int #

isSigned :: VkPipelineTessellationStateCreateFlags -> Bool #

shiftL :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

unsafeShiftL :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

shiftR :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

unsafeShiftR :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

rotateL :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

rotateR :: VkPipelineTessellationStateCreateFlags -> Int -> VkPipelineTessellationStateCreateFlags #

popCount :: VkPipelineTessellationStateCreateFlags -> Int #

FiniteBits VkPipelineTessellationStateCreateFlags Source # 
Instance details

newtype VkPipelineInputAssemblyStateCreateFlags Source #

VkPipelineInputAssemblyStateCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineInputAssemblyStateCreateInfo

Instances
Eq VkPipelineInputAssemblyStateCreateFlags Source # 
Instance details
Ord VkPipelineInputAssemblyStateCreateFlags Source # 
Instance details
Read VkPipelineInputAssemblyStateCreateFlags Source # 
Instance details
Show VkPipelineInputAssemblyStateCreateFlags Source # 
Instance details
Storable VkPipelineInputAssemblyStateCreateFlags Source # 
Instance details
Bits VkPipelineInputAssemblyStateCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineInputAssemblyStateCreateFlags -> VkPipelineInputAssemblyStateCreateFlags -> VkPipelineInputAssemblyStateCreateFlags #

complement :: VkPipelineInputAssemblyStateCreateFlags -> VkPipelineInputAssemblyStateCreateFlags #

shift :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

rotate :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

zeroBits :: VkPipelineInputAssemblyStateCreateFlags #

bit :: Int -> VkPipelineInputAssemblyStateCreateFlags #

setBit :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

clearBit :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

complementBit :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

testBit :: VkPipelineInputAssemblyStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineInputAssemblyStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineInputAssemblyStateCreateFlags -> Int #

isSigned :: VkPipelineInputAssemblyStateCreateFlags -> Bool #

shiftL :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

unsafeShiftL :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

shiftR :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

unsafeShiftR :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

rotateL :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

rotateR :: VkPipelineInputAssemblyStateCreateFlags -> Int -> VkPipelineInputAssemblyStateCreateFlags #

popCount :: VkPipelineInputAssemblyStateCreateFlags -> Int #

FiniteBits VkPipelineInputAssemblyStateCreateFlags Source # 
Instance details

newtype VkPipelineVertexInputStateCreateFlags Source #

VkPipelineVertexInputStateCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineVertexInputStateCreateInfo

Instances
Eq VkPipelineVertexInputStateCreateFlags Source # 
Instance details
Ord VkPipelineVertexInputStateCreateFlags Source # 
Instance details
Read VkPipelineVertexInputStateCreateFlags Source # 
Instance details
Show VkPipelineVertexInputStateCreateFlags Source # 
Instance details
Storable VkPipelineVertexInputStateCreateFlags Source # 
Instance details
Bits VkPipelineVertexInputStateCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags #

complement :: VkPipelineVertexInputStateCreateFlags -> VkPipelineVertexInputStateCreateFlags #

shift :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

rotate :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

zeroBits :: VkPipelineVertexInputStateCreateFlags #

bit :: Int -> VkPipelineVertexInputStateCreateFlags #

setBit :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

clearBit :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

complementBit :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

testBit :: VkPipelineVertexInputStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineVertexInputStateCreateFlags -> Maybe Int #

bitSize :: VkPipelineVertexInputStateCreateFlags -> Int #

isSigned :: VkPipelineVertexInputStateCreateFlags -> Bool #

shiftL :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

unsafeShiftL :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

shiftR :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

unsafeShiftR :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

rotateL :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

rotateR :: VkPipelineVertexInputStateCreateFlags -> Int -> VkPipelineVertexInputStateCreateFlags #

popCount :: VkPipelineVertexInputStateCreateFlags -> Int #

FiniteBits VkPipelineVertexInputStateCreateFlags Source # 
Instance details

newtype VkPipelineShaderStageCreateFlags Source #

VkPipelineShaderStageCreateFlags - Reserved for future use

Description

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

See Also

VkPipelineShaderStageCreateInfo

Instances
Eq VkPipelineShaderStageCreateFlags Source # 
Instance details
Ord VkPipelineShaderStageCreateFlags Source # 
Instance details
Read VkPipelineShaderStageCreateFlags Source # 
Instance details
Show VkPipelineShaderStageCreateFlags Source # 
Instance details
Storable VkPipelineShaderStageCreateFlags Source # 
Instance details
Bits VkPipelineShaderStageCreateFlags Source # 
Instance details

Methods

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

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

xor :: VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags #

complement :: VkPipelineShaderStageCreateFlags -> VkPipelineShaderStageCreateFlags #

shift :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

rotate :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

zeroBits :: VkPipelineShaderStageCreateFlags #

bit :: Int -> VkPipelineShaderStageCreateFlags #

setBit :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

clearBit :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

complementBit :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

testBit :: VkPipelineShaderStageCreateFlags -> Int -> Bool #

bitSizeMaybe :: VkPipelineShaderStageCreateFlags -> Maybe Int #

bitSize :: VkPipelineShaderStageCreateFlags -> Int #

isSigned :: VkPipelineShaderStageCreateFlags -> Bool #

shiftL :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

unsafeShiftL :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

shiftR :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

unsafeShiftR :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

rotateL :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

rotateR :: VkPipelineShaderStageCreateFlags -> Int -> VkPipelineShaderStageCreateFlags #

popCount :: VkPipelineShaderStageCreateFlags -> Int #

FiniteBits VkPipelineShaderStageCreateFlags Source # 
Instance details

newtype VkShaderStageFlagBits Source #

VkShaderStageFlagBits - Bitmask specifying a pipeline stage

See Also

VkPipelineShaderStageCreateInfo, VkShaderStageFlags, vkGetShaderInfoAMD

Instances
Eq VkShaderStageFlagBits Source # 
Instance details
Ord VkShaderStageFlagBits Source # 
Instance details
Read VkShaderStageFlagBits Source # 
Instance details
Show VkShaderStageFlagBits Source # 
Instance details
Storable VkShaderStageFlagBits Source # 
Instance details
Bits VkShaderStageFlagBits Source # 
Instance details
FiniteBits VkShaderStageFlagBits Source # 
Instance details

pattern VK_SHADER_STAGE_VERTEX_BIT :: VkShaderStageFlagBits Source #

VK_SHADER_STAGE_VERTEX_BIT specifies the vertex stage.

pattern VK_SHADER_STAGE_TESSELLATION_CONTROL_BIT :: VkShaderStageFlagBits Source #

VK_SHADER_STAGE_TESSELLATION_CONTROL_BIT specifies the tessellation control stage.

pattern VK_SHADER_STAGE_TESSELLATION_EVALUATION_BIT :: VkShaderStageFlagBits Source #

VK_SHADER_STAGE_TESSELLATION_EVALUATION_BIT specifies the tessellation evaluation stage.

pattern VK_SHADER_STAGE_GEOMETRY_BIT :: VkShaderStageFlagBits Source #

VK_SHADER_STAGE_GEOMETRY_BIT specifies the geometry stage.

pattern VK_SHADER_STAGE_FRAGMENT_BIT :: VkShaderStageFlagBits Source #

VK_SHADER_STAGE_FRAGMENT_BIT specifies the fragment stage.

pattern VK_SHADER_STAGE_COMPUTE_BIT :: VkShaderStageFlagBits Source #

VK_SHADER_STAGE_COMPUTE_BIT specifies the compute stage.

pattern VK_SHADER_STAGE_ALL_GRAPHICS :: VkShaderStageFlagBits Source #

VK_SHADER_STAGE_ALL_GRAPHICS is a combination of bits used as shorthand to specify all graphics stages defined above (excluding the compute stage).

pattern VK_SHADER_STAGE_ALL :: VkShaderStageFlagBits Source #

VK_SHADER_STAGE_ALL is a combination of bits used as shorthand to specify all shader stages supported by the device, including all additional stages which are introduced by extensions.

newtype VkPipelineCreateFlagBits Source #

VkPipelineCreateFlagBits - Bitmask controlling how a pipeline is created

Description

  • VK_PIPELINE_CREATE_DISABLE_OPTIMIZATION_BIT specifies that the created pipeline will not be optimized. Using this flag may reduce the time taken to create the pipeline.
  • VK_PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT specifies that the pipeline to be created is allowed to be the parent of a pipeline that will be created in a subsequent call to vkCreateGraphicsPipelines or vkCreateComputePipelines.
  • VK_PIPELINE_CREATE_DERIVATIVE_BIT specifies that the pipeline to be created will be a child of a previously created parent pipeline.
  • VK_PIPELINE_CREATE_VIEW_INDEX_FROM_DEVICE_INDEX_BIT specifies that any shader input variables decorated as DeviceIndex will be assigned values as if they were decorated as ViewIndex.
  • VK_PIPELINE_CREATE_DISPATCH_BASE specifies that a compute pipeline can be used with vkCmdDispatchBase with a non-zero base workgroup.

It is valid to set both VK_PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT and VK_PIPELINE_CREATE_DERIVATIVE_BIT. This allows a pipeline to be both a parent and possibly a child in a pipeline hierarchy. See Pipeline Derivatives for more information.

See Also

VkPipelineCreateFlags

Instances
Eq VkPipelineCreateFlagBits Source # 
Instance details
Ord VkPipelineCreateFlagBits Source # 
Instance details
Read VkPipelineCreateFlagBits Source # 
Instance details
Show VkPipelineCreateFlagBits Source # 
Instance details
Storable VkPipelineCreateFlagBits Source # 
Instance details
Bits VkPipelineCreateFlagBits Source # 
Instance details
FiniteBits VkPipelineCreateFlagBits Source # 
Instance details

newtype VkColorComponentFlagBits Source #

VkColorComponentFlagBits - Bitmask controlling which components are written to the framebuffer

Description

  • VK_COLOR_COMPONENT_R_BIT specifies that the R value is written to the color attachment for the appropriate sample. Otherwise, the value in memory is unmodified.
  • VK_COLOR_COMPONENT_G_BIT specifies that the G value is written to the color attachment for the appropriate sample. Otherwise, the value in memory is unmodified.
  • VK_COLOR_COMPONENT_B_BIT specifies that the B value is written to the color attachment for the appropriate sample. Otherwise, the value in memory is unmodified.
  • VK_COLOR_COMPONENT_A_BIT specifies that the A value is written to the color attachment for the appropriate sample. Otherwise, the value in memory is unmodified.

The color write mask operation is applied regardless of whether blending is enabled.

See Also

VkColorComponentFlags

Instances
Eq VkColorComponentFlagBits Source # 
Instance details
Ord VkColorComponentFlagBits Source # 
Instance details
Read VkColorComponentFlagBits Source # 
Instance details
Show VkColorComponentFlagBits Source # 
Instance details
Storable VkColorComponentFlagBits Source # 
Instance details
Bits VkColorComponentFlagBits Source # 
Instance details
FiniteBits VkColorComponentFlagBits Source # 
Instance details

newtype VkCullModeFlagBits Source #

VkCullModeFlagBits - Bitmask controlling triangle culling

Description

  • VK_CULL_MODE_NONE specifies that no triangles are discarded
  • VK_CULL_MODE_FRONT_BIT specifies that front-facing triangles are discarded
  • VK_CULL_MODE_BACK_BIT specifies that back-facing triangles are discarded
  • VK_CULL_MODE_FRONT_AND_BACK specifies that all triangles are discarded.

Following culling, fragments are produced for any triangles which have not been discarded.

See Also

VkCullModeFlags

Instances
Eq VkCullModeFlagBits Source # 
Instance details
Ord VkCullModeFlagBits Source # 
Instance details
Read VkCullModeFlagBits Source # 
Instance details
Show VkCullModeFlagBits Source # 
Instance details
Storable VkCullModeFlagBits Source # 
Instance details
Bits VkCullModeFlagBits Source # 
Instance details
FiniteBits VkCullModeFlagBits Source # 
Instance details

vkCreateGraphicsPipelines :: ("device" ::: VkDevice) -> ("pipelineCache" ::: VkPipelineCache) -> ("createInfoCount" ::: Word32) -> ("pCreateInfos" ::: Ptr VkGraphicsPipelineCreateInfo) -> ("pAllocator" ::: Ptr VkAllocationCallbacks) -> ("pPipelines" ::: Ptr VkPipeline) -> IO VkResult Source #

vkCreateGraphicsPipelines - Create graphics pipelines

Parameters

  • device is the logical device that creates the graphics pipelines.
  • pipelineCache is either VK_NULL_HANDLE, indicating that pipeline caching is disabled; or the handle of a valid pipeline cache object, in which case use of that cache is enabled for the duration of the command.
  • createInfoCount is the length of the pCreateInfos and pPipelines arrays.
  • pCreateInfos is an array of VkGraphicsPipelineCreateInfo structures.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.
  • pPipelines is a pointer to an array in which the resulting graphics pipeline objects are returned.

Description

The VkGraphicsPipelineCreateInfo structure includes an array of shader create info structures containing all the desired active shader stages, as well as creation info to define all relevant fixed-function stages, and a pipeline layout.

Valid Usage

  • If the flags member of any element of pCreateInfos contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and the basePipelineIndex member of that same element is not -1, basePipelineIndex must be less than the index into pCreateInfos that corresponds to that element
  • If the flags member of any element of pCreateInfos contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, the base pipeline must have been created with the VK_PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT flag set

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • If pipelineCache is not VK_NULL_HANDLE, pipelineCache must be a valid VkPipelineCache handle
  • pCreateInfos must be a valid pointer to an array of createInfoCount valid VkGraphicsPipelineCreateInfo structures
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid VkAllocationCallbacks structure
  • pPipelines must be a valid pointer to an array of createInfoCount VkPipeline handles
  • createInfoCount must be greater than 0
  • If pipelineCache is a valid handle, it must have been created, allocated, or retrieved from device

Return Codes

[Success] - VK_SUCCESS

[Failure] - VK_ERROR_OUT_OF_HOST_MEMORY

  • VK_ERROR_OUT_OF_DEVICE_MEMORY
  • VK_ERROR_INVALID_SHADER_NV

See Also

VkAllocationCallbacks, VkDevice, VkGraphicsPipelineCreateInfo, VkPipeline, VkPipelineCache

vkCreateComputePipelines :: ("device" ::: VkDevice) -> ("pipelineCache" ::: VkPipelineCache) -> ("createInfoCount" ::: Word32) -> ("pCreateInfos" ::: Ptr VkComputePipelineCreateInfo) -> ("pAllocator" ::: Ptr VkAllocationCallbacks) -> ("pPipelines" ::: Ptr VkPipeline) -> IO VkResult Source #

vkCreateComputePipelines - Creates a new compute pipeline object

Parameters

  • device is the logical device that creates the compute pipelines.
  • pipelineCache is either VK_NULL_HANDLE, indicating that pipeline caching is disabled; or the handle of a valid pipeline cache object, in which case use of that cache is enabled for the duration of the command.
  • createInfoCount is the length of the pCreateInfos and pPipelines arrays.
  • pCreateInfos is an array of VkComputePipelineCreateInfo structures.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.
  • pPipelines is a pointer to an array in which the resulting compute pipeline objects are returned.

Valid Usage

  • If the flags member of any element of pCreateInfos contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and the basePipelineIndex member of that same element is not -1, basePipelineIndex must be less than the index into pCreateInfos that corresponds to that element
  • If the flags member of any element of pCreateInfos contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, the base pipeline must have been created with the VK_PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT flag set

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • If pipelineCache is not VK_NULL_HANDLE, pipelineCache must be a valid VkPipelineCache handle
  • pCreateInfos must be a valid pointer to an array of createInfoCount valid VkComputePipelineCreateInfo structures
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid VkAllocationCallbacks structure
  • pPipelines must be a valid pointer to an array of createInfoCount VkPipeline handles
  • createInfoCount must be greater than 0
  • If pipelineCache is a valid handle, it must have been created, allocated, or retrieved from device

Return Codes

[Success] - VK_SUCCESS

[Failure] - VK_ERROR_OUT_OF_HOST_MEMORY

  • VK_ERROR_OUT_OF_DEVICE_MEMORY
  • VK_ERROR_INVALID_SHADER_NV

See Also

VkAllocationCallbacks, VkComputePipelineCreateInfo, VkDevice, VkPipeline, VkPipelineCache

vkDestroyPipeline :: ("device" ::: VkDevice) -> ("pipeline" ::: VkPipeline) -> ("pAllocator" ::: Ptr VkAllocationCallbacks) -> IO () Source #

vkDestroyPipeline - Destroy a pipeline object

Parameters

  • device is the logical device that destroys the pipeline.
  • pipeline is the handle of the pipeline to destroy.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.

Valid Usage

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

Valid Usage (Implicit)

  • device must be a valid VkDevice handle
  • If pipeline is not VK_NULL_HANDLE, pipeline must be a valid VkPipeline handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid VkAllocationCallbacks structure
  • If pipeline is a valid handle, it must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to pipeline must be externally synchronized

See Also

VkAllocationCallbacks, VkDevice, VkPipeline

data VkOffset2D Source #

VkOffset2D - Structure specifying a two-dimensional offset

See Also

VkDisplayPlaneCapabilitiesKHR, VkRect2D, VkRectLayerKHR

Constructors

VkOffset2D 

Fields

data VkViewport Source #

VkViewport - Structure specifying a viewport

Description

The framebuffer depth coordinate zf may be represented using either a fixed-point or floating-point representation. However, a floating-point representation must be used if the depth/stencil attachment has a floating-point depth component. If an m-bit fixed-point representation is used, we assume that it represents each value \(\frac{k}{2^m - 1}\), where k ∈ { 0, 1, …​, 2m-1 }, as k (e.g. 1.0 is represented in binary as a string of all ones).

The viewport parameters shown in the above equations are found from these values as

  • ox = x + width / 2
  • oy = y + height / 2
  • oz = minDepth
  • px = width
  • py = height
  • pz = maxDepth - minDepth.

The application can specify a negative term for height, which has the effect of negating the y coordinate in clip space before performing the transform. When using a negative height, the application should also adjust the y value to point to the lower left corner of the viewport instead of the upper left corner. Using the negative height allows the application to avoid having to negate the y component of the Position output from the last vertex processing stage in shaders that also target other graphics APIs.

The width and height of the implementation-dependent maximum viewport dimensions must be greater than or equal to the width and height of the largest image which can be created and attached to a framebuffer.

The floating-point viewport bounds are represented with an implementation-dependent precision.

Valid Usage

  • width must be greater than 0.0
  • width must be less than or equal to VkPhysicalDeviceLimits::maxViewportDimensions[0]
  • The absolute value of height must be less than or equal to VkPhysicalDeviceLimits::maxViewportDimensions[1]
  • x must be greater than or equal to viewportBoundsRange[0]
  • (x + width) must be less than or equal to viewportBoundsRange[1]
  • y must be greater than or equal to viewportBoundsRange[0]
  • y must be less than or equal to viewportBoundsRange[1]
  • (y + height) must be greater than or equal to viewportBoundsRange[0]
  • (y + height) must be less than or equal to viewportBoundsRange[1]
  • Unless {html_spec_relative}#VK_EXT_depth_range_unrestricted extension is enabled minDepth must be between 0.0 and 1.0, inclusive
  • Unless {html_spec_relative}#VK_EXT_depth_range_unrestricted extension is enabled maxDepth must be between 0.0 and 1.0, inclusive

See Also

VkPipelineViewportStateCreateInfo, vkCmdSetViewport

Constructors

VkViewport 

Fields

data VkSpecializationMapEntry Source #

VkSpecializationMapEntry - Structure specifying a specialization map entry

Description

If a constantID value is not a specialization constant ID used in the shader, that map entry does not affect the behavior of the pipeline.

Valid Usage

  • For a constantID specialization constant declared in a shader, size must match the byte size of the constantID. If the specialization constant is of type boolean, size must be the byte size of VkBool32

See Also

VkSpecializationInfo

Constructors

VkSpecializationMapEntry 

Fields

  • vkConstantID :: Word32

    constantID is the ID of the specialization constant in SPIR-V.

  • vkOffset :: Word32

    offset is the byte offset of the specialization constant value within the supplied data buffer.

  • vkSize :: CSize

    size is the byte size of the specialization constant value within the supplied data buffer.

data VkSpecializationInfo Source #

VkSpecializationInfo - Structure specifying specialization info

Description

pMapEntries points to a structure of type VkSpecializationMapEntry.

Valid Usage

  • The offset member of each element of pMapEntries must be less than dataSize
  • The size member of each element of pMapEntries must be less than or equal to dataSize minus offset
  • If mapEntryCount is not 0, pMapEntries must be a valid pointer to an array of mapEntryCount valid VkSpecializationMapEntry structures

Valid Usage (Implicit)

  • If dataSize is not 0, pData must be a valid pointer to an array of dataSize bytes

See Also

VkPipelineShaderStageCreateInfo, VkSpecializationMapEntry

Constructors

VkSpecializationInfo 

Fields

data VkPipelineShaderStageCreateInfo Source #

VkPipelineShaderStageCreateInfo - Structure specifying parameters of a newly created pipeline shader stage

Valid Usage

  • If the geometry shaders feature is not enabled, stage must not be VK_SHADER_STAGE_GEOMETRY_BIT
  • If the tessellation shaders feature is not enabled, stage must not be VK_SHADER_STAGE_TESSELLATION_CONTROL_BIT or VK_SHADER_STAGE_TESSELLATION_EVALUATION_BIT
  • stage must not be VK_SHADER_STAGE_ALL_GRAPHICS, or VK_SHADER_STAGE_ALL
  • pName must be the name of an OpEntryPoint in module with an execution model that matches stage
  • If the identified entry point includes any variable in its interface that is declared with the ClipDistance BuiltIn decoration, that variable must not have an array size greater than VkPhysicalDeviceLimits::maxClipDistances
  • If the identified entry point includes any variable in its interface that is declared with the CullDistance BuiltIn decoration, that variable must not have an array size greater than VkPhysicalDeviceLimits::maxCullDistances
  • If the identified entry point includes any variables in its interface that are declared with the ClipDistance or CullDistance BuiltIn decoration, those variables must not have array sizes which sum to more than VkPhysicalDeviceLimits::maxCombinedClipAndCullDistances
  • If the identified entry point includes any variable in its interface that is declared with the SampleMask BuiltIn decoration, that variable must not have an array size greater than VkPhysicalDeviceLimits::maxSampleMaskWords
  • If stage is VK_SHADER_STAGE_VERTEX_BIT, the identified entry point must not include any input variable in its interface that is decorated with CullDistance
  • If stage is VK_SHADER_STAGE_TESSELLATION_CONTROL_BIT or VK_SHADER_STAGE_TESSELLATION_EVALUATION_BIT, and the identified entry point has an OpExecutionMode instruction that specifies a patch size with OutputVertices, the patch size must be greater than 0 and less than or equal to VkPhysicalDeviceLimits::maxTessellationPatchSize
  • If stage is VK_SHADER_STAGE_GEOMETRY_BIT, the identified entry point must have an OpExecutionMode instruction that specifies a maximum output vertex count that is greater than 0 and less than or equal to VkPhysicalDeviceLimits::maxGeometryOutputVertices
  • If stage is VK_SHADER_STAGE_GEOMETRY_BIT, the identified entry point must have an OpExecutionMode instruction that specifies an invocation count that is greater than 0 and less than or equal to VkPhysicalDeviceLimits::maxGeometryShaderInvocations
  • If stage is VK_SHADER_STAGE_GEOMETRY_BIT, and the identified entry point writes to Layer for any primitive, it must write the same value to Layer for all vertices of a given primitive
  • If stage is VK_SHADER_STAGE_GEOMETRY_BIT, and the identified entry point writes to ViewportIndex for any primitive, it must write the same value to ViewportIndex for all vertices of a given primitive
  • If stage is VK_SHADER_STAGE_FRAGMENT_BIT, the identified entry point must not include any output variables in its interface decorated with CullDistance
  • If stage is VK_SHADER_STAGE_FRAGMENT_BIT, and the identified entry point writes to FragDepth in any execution path, it must write to FragDepth in all execution paths
  • If stage is VK_SHADER_STAGE_FRAGMENT_BIT, and the identified entry point writes to FragStencilRefEXT in any execution path, it must write to FragStencilRefEXT in all execution paths

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_CREATE_INFO
  • pNext must be NULL
  • flags must be 0
  • stage must be a valid VkShaderStageFlagBits value
  • module must be a valid VkShaderModule handle
  • pName must be a null-terminated UTF-8 string
  • If pSpecializationInfo is not NULL, pSpecializationInfo must be a valid pointer to a valid VkSpecializationInfo structure

See Also

VkComputePipelineCreateInfo, VkGraphicsPipelineCreateInfo, VkPipelineShaderStageCreateFlags, VkShaderModule, VkShaderStageFlagBits, VkSpecializationInfo, VkStructureType

Constructors

VkPipelineShaderStageCreateInfo 

Fields

data VkComputePipelineCreateInfo Source #

VkComputePipelineCreateInfo - Structure specifying parameters of a newly created compute pipeline

Description

The parameters basePipelineHandle and basePipelineIndex are described in more detail in Pipeline Derivatives.

stage points to a structure of type VkPipelineShaderStageCreateInfo.

Valid Usage

  • If flags contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and basePipelineIndex is -1, basePipelineHandle must be a valid handle to a compute VkPipeline
  • If flags contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and basePipelineHandle is VK_NULL_HANDLE, basePipelineIndex must be a valid index into the calling command’s pCreateInfos parameter
  • If flags contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and basePipelineIndex is not -1, basePipelineHandle must be VK_NULL_HANDLE
  • If flags contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and basePipelineHandle is not VK_NULL_HANDLE, basePipelineIndex must be -1
  • The stage member of stage must be VK_SHADER_STAGE_COMPUTE_BIT
  • The shader code for the entry point identified by stage and the rest of the state identified by this structure must adhere to the pipeline linking rules described in the Shader Interfaces chapter
  • layout must be consistent with the layout of the compute shader specified in stage
  • The number of resources in layout accessible to the compute shader stage must be less than or equal to VkPhysicalDeviceLimits::maxPerStageResources

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_COMPUTE_PIPELINE_CREATE_INFO
  • pNext must be NULL
  • flags must be a valid combination of VkPipelineCreateFlagBits values
  • stage must be a valid VkPipelineShaderStageCreateInfo structure
  • layout must be a valid VkPipelineLayout handle
  • Both of basePipelineHandle, and layout that are valid handles must have been created, allocated, or retrieved from the same VkDevice

See Also

VkPipeline, VkPipelineCreateFlags, VkPipelineLayout, VkPipelineShaderStageCreateInfo, VkStructureType, vkCreateComputePipelines

Constructors

VkComputePipelineCreateInfo 

Fields

data VkVertexInputBindingDescription Source #

VkVertexInputBindingDescription - Structure specifying vertex input binding description

Valid Usage

  • binding must be less than VkPhysicalDeviceLimits::maxVertexInputBindings
  • stride must be less than or equal to VkPhysicalDeviceLimits::maxVertexInputBindingStride

Valid Usage (Implicit)

See Also

VkPipelineVertexInputStateCreateInfo, VkVertexInputRate

Constructors

VkVertexInputBindingDescription 

Fields

data VkVertexInputAttributeDescription Source #

VkVertexInputAttributeDescription - Structure specifying vertex input attribute description

Valid Usage

  • location must be less than VkPhysicalDeviceLimits::maxVertexInputAttributes
  • binding must be less than VkPhysicalDeviceLimits::maxVertexInputBindings
  • offset must be less than or equal to VkPhysicalDeviceLimits::maxVertexInputAttributeOffset
  • format must be allowed as a vertex buffer format, as specified by the VK_FORMAT_FEATURE_VERTEX_BUFFER_BIT flag in VkFormatProperties::bufferFeatures returned by vkGetPhysicalDeviceFormatProperties

Valid Usage (Implicit)

See Also

VkFormat, VkPipelineVertexInputStateCreateInfo

Constructors

VkVertexInputAttributeDescription 

Fields

  • vkLocation :: Word32

    location is the shader binding location number for this attribute.

  • vkBinding :: Word32

    binding is the binding number which this attribute takes its data from.

  • vkFormat :: VkFormat

    format is the size and type of the vertex attribute data.

  • vkOffset :: Word32

    offset is a byte offset of this attribute relative to the start of an element in the vertex input binding.

data VkPipelineVertexInputStateCreateInfo Source #

VkPipelineVertexInputStateCreateInfo - Structure specifying parameters of a newly created pipeline vertex input state

Valid Usage

  • vertexBindingDescriptionCount must be less than or equal to VkPhysicalDeviceLimits::maxVertexInputBindings
  • vertexAttributeDescriptionCount must be less than or equal to VkPhysicalDeviceLimits::maxVertexInputAttributes
  • For every binding specified by each element of pVertexAttributeDescriptions, a VkVertexInputBindingDescription must exist in pVertexBindingDescriptions with the same value of binding
  • All elements of pVertexBindingDescriptions must describe distinct binding numbers
  • All elements of pVertexAttributeDescriptions must describe distinct attribute locations

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_STATE_CREATE_INFO
  • pNext must be NULL or a pointer to a valid instance of VkPipelineVertexInputDivisorStateCreateInfoEXT
  • flags must be 0
  • If vertexBindingDescriptionCount is not 0, pVertexBindingDescriptions must be a valid pointer to an array of vertexBindingDescriptionCount valid VkVertexInputBindingDescription structures
  • If vertexAttributeDescriptionCount is not 0, pVertexAttributeDescriptions must be a valid pointer to an array of vertexAttributeDescriptionCount valid VkVertexInputAttributeDescription structures

See Also

VkGraphicsPipelineCreateInfo, VkPipelineVertexInputStateCreateFlags, VkStructureType, VkVertexInputAttributeDescription, VkVertexInputBindingDescription

Constructors

VkPipelineVertexInputStateCreateInfo 

Fields

data VkPipelineInputAssemblyStateCreateInfo Source #

VkPipelineInputAssemblyStateCreateInfo - Structure specifying parameters of a newly created pipeline input assembly state

Description

Restarting the assembly of primitives discards the most recent index values if those elements formed an incomplete primitive, and restarts the primitive assembly using the subsequent indices, but only assembling the immediately following element through the end of the originally specified elements. The primitive restart index value comparison is performed before adding the vertexOffset value to the index value.

Valid Usage

  • If topology is VK_PRIMITIVE_TOPOLOGY_POINT_LIST, VK_PRIMITIVE_TOPOLOGY_LINE_LIST, VK_PRIMITIVE_TOPOLOGY_TRIANGLE_LIST, VK_PRIMITIVE_TOPOLOGY_LINE_LIST_WITH_ADJACENCY, VK_PRIMITIVE_TOPOLOGY_TRIANGLE_LIST_WITH_ADJACENCY or VK_PRIMITIVE_TOPOLOGY_PATCH_LIST, primitiveRestartEnable must be VK_FALSE
  • If the geometry shaders feature is not enabled, topology must not be any of VK_PRIMITIVE_TOPOLOGY_LINE_LIST_WITH_ADJACENCY, VK_PRIMITIVE_TOPOLOGY_LINE_STRIP_WITH_ADJACENCY, VK_PRIMITIVE_TOPOLOGY_TRIANGLE_LIST_WITH_ADJACENCY or VK_PRIMITIVE_TOPOLOGY_TRIANGLE_STRIP_WITH_ADJACENCY
  • If the tessellation shaders feature is not enabled, topology must not be VK_PRIMITIVE_TOPOLOGY_PATCH_LIST

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_INPUT_ASSEMBLY_STATE_CREATE_INFO

See Also

VkBool32, VkGraphicsPipelineCreateInfo, VkPipelineInputAssemblyStateCreateFlags, VkPrimitiveTopology, VkStructureType

Constructors

VkPipelineInputAssemblyStateCreateInfo 

Fields

data VkPipelineTessellationStateCreateInfo Source #

VkPipelineTessellationStateCreateInfo - Structure specifying parameters of a newly created pipeline tessellation state

Valid Usage

  • patchControlPoints must be greater than zero and less than or equal to VkPhysicalDeviceLimits::maxTessellationPatchSize

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_TESSELLATION_STATE_CREATE_INFO

See Also

VkGraphicsPipelineCreateInfo, VkPipelineTessellationStateCreateFlags, VkStructureType

Constructors

VkPipelineTessellationStateCreateInfo 

Fields

data VkPipelineViewportStateCreateInfo Source #

VkPipelineViewportStateCreateInfo - Structure specifying parameters of a newly created pipeline viewport state

Valid Usage

  • If the multiple viewports feature is not enabled, scissorCount must be 1
  • viewportCount must be between 1 and VkPhysicalDeviceLimits::maxViewports, inclusive
  • scissorCount must be between 1 and VkPhysicalDeviceLimits::maxViewports, inclusive
  • scissorCount and viewportCount must be identical
  • If the viewportWScalingEnable member of a VkPipelineViewportWScalingStateCreateInfoNV structure chained to the pNext chain is VK_TRUE, the viewportCount member of the VkPipelineViewportWScalingStateCreateInfoNV structure must be equal to viewportCount

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_VIEWPORT_STATE_CREATE_INFO

See Also

VkGraphicsPipelineCreateInfo, VkPipelineViewportStateCreateFlags, VkRect2D, VkStructureType, VkViewport

Constructors

VkPipelineViewportStateCreateInfo 

Fields

data VkPipelineRasterizationStateCreateInfo Source #

VkPipelineRasterizationStateCreateInfo - Structure specifying parameters of a newly created pipeline rasterization state

Description

The application can also add a VkPipelineRasterizationStateRasterizationOrderAMD structure to the pNext chain of a VkPipelineRasterizationStateCreateInfo structure. This structure enables selecting the rasterization order to use when rendering with the corresponding graphics pipeline as described in Rasterization Order.

Valid Usage

  • If the depth clamping feature is not enabled, depthClampEnable must be VK_FALSE
  • If the non-solid fill modes feature is not enabled, polygonMode must be VK_POLYGON_MODE_FILL or VK_POLYGON_MODE_FILL_RECTANGLE_NV
  • If the {html_spec_relative}#VK_NV_fill_rectangle extension is not enabled, polygonMode must not be VK_POLYGON_MODE_FILL_RECTANGLE_NV

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_CREATE_INFO

See Also

VkBool32, VkCullModeFlags, VkFrontFace, VkGraphicsPipelineCreateInfo, VkPipelineRasterizationStateCreateFlags, VkPolygonMode, VkStructureType

Constructors

VkPipelineRasterizationStateCreateInfo 

Fields

data VkPipelineMultisampleStateCreateInfo Source #

VkPipelineMultisampleStateCreateInfo - Structure specifying parameters of a newly created pipeline multisample state

Valid Usage

  • If the alpha to one feature is not enabled, alphaToOneEnable must be VK_FALSE
  • minSampleShading must be in the range [0,1]
  • If the subpass has any color attachments and rasterizationSamples is greater than the number of color samples, then sampleShadingEnable must be VK_FALSE

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_MULTISAMPLE_STATE_CREATE_INFO

See Also

VkBool32, VkGraphicsPipelineCreateInfo, VkPipelineMultisampleStateCreateFlags, VkSampleCountFlagBits, VkSampleMask, VkStructureType

Constructors

VkPipelineMultisampleStateCreateInfo 

Fields

data VkPipelineColorBlendAttachmentState Source #

VkPipelineColorBlendAttachmentState - Structure specifying a pipeline color blend attachment state

Valid Usage

  • If the dual source blending feature is not enabled, srcColorBlendFactor must not be VK_BLEND_FACTOR_SRC1_COLOR, VK_BLEND_FACTOR_ONE_MINUS_SRC1_COLOR, VK_BLEND_FACTOR_SRC1_ALPHA, or VK_BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA
  • If the dual source blending feature is not enabled, dstColorBlendFactor must not be VK_BLEND_FACTOR_SRC1_COLOR, VK_BLEND_FACTOR_ONE_MINUS_SRC1_COLOR, VK_BLEND_FACTOR_SRC1_ALPHA, or VK_BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA
  • If the dual source blending feature is not enabled, srcAlphaBlendFactor must not be VK_BLEND_FACTOR_SRC1_COLOR, VK_BLEND_FACTOR_ONE_MINUS_SRC1_COLOR, VK_BLEND_FACTOR_SRC1_ALPHA, or VK_BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA
  • If the dual source blending feature is not enabled, dstAlphaBlendFactor must not be VK_BLEND_FACTOR_SRC1_COLOR, VK_BLEND_FACTOR_ONE_MINUS_SRC1_COLOR, VK_BLEND_FACTOR_SRC1_ALPHA, or VK_BLEND_FACTOR_ONE_MINUS_SRC1_ALPHA
  • If either of colorBlendOp or alphaBlendOp is an advanced blend operation, then colorBlendOp must equal alphaBlendOp
  • If VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT::advancedBlendIndependentBlend is VK_FALSE and colorBlendOp is an advanced blend operation, then colorBlendOp must be the same for all attachments.
  • If VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT::advancedBlendIndependentBlend is VK_FALSE and alphaBlendOp is an advanced blend operation, then alphaBlendOp must be the same for all attachments.
  • If VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT::advancedBlendAllOperations is VK_FALSE, then colorBlendOp must not be VK_BLEND_OP_ZERO_EXT, VK_BLEND_OP_SRC_EXT, VK_BLEND_OP_DST_EXT, VK_BLEND_OP_SRC_OVER_EXT, VK_BLEND_OP_DST_OVER_EXT, VK_BLEND_OP_SRC_IN_EXT, VK_BLEND_OP_DST_IN_EXT, VK_BLEND_OP_SRC_OUT_EXT, VK_BLEND_OP_DST_OUT_EXT, VK_BLEND_OP_SRC_ATOP_EXT, VK_BLEND_OP_DST_ATOP_EXT, VK_BLEND_OP_XOR_EXT, VK_BLEND_OP_INVERT_EXT, VK_BLEND_OP_INVERT_RGB_EXT, VK_BLEND_OP_LINEARDODGE_EXT, VK_BLEND_OP_LINEARBURN_EXT, VK_BLEND_OP_VIVIDLIGHT_EXT, VK_BLEND_OP_LINEARLIGHT_EXT, VK_BLEND_OP_PINLIGHT_EXT, VK_BLEND_OP_HARDMIX_EXT, VK_BLEND_OP_PLUS_EXT, VK_BLEND_OP_PLUS_CLAMPED_EXT, VK_BLEND_OP_PLUS_CLAMPED_ALPHA_EXT, VK_BLEND_OP_PLUS_DARKER_EXT, VK_BLEND_OP_MINUS_EXT, VK_BLEND_OP_MINUS_CLAMPED_EXT, VK_BLEND_OP_CONTRAST_EXT, VK_BLEND_OP_INVERT_OVG_EXT, VK_BLEND_OP_RED_EXT, VK_BLEND_OP_GREEN_EXT, or VK_BLEND_OP_BLUE_EXT
  • If colorBlendOp or alphaBlendOp is an advanced blend operation, then VkSubpassDescription::colorAttachmentCount of the subpass this pipeline is compiled against must be less than or equal to VkPhysicalDeviceBlendOperationAdvancedPropertiesEXT::advancedBlendMaxColorAttachments

Valid Usage (Implicit)

See Also

VkBlendFactor, VkBlendOp, VkBool32, VkColorComponentFlags, VkPipelineColorBlendStateCreateInfo

Constructors

VkPipelineColorBlendAttachmentState 

Fields

data VkPipelineColorBlendStateCreateInfo Source #

VkPipelineColorBlendStateCreateInfo - Structure specifying parameters of a newly created pipeline color blend state

Description

Each element of the pAttachments array is a VkPipelineColorBlendAttachmentState structure specifying per-target blending state for each individual color attachment. If the independent blending feature is not enabled on the device, all VkPipelineColorBlendAttachmentState elements in the pAttachments array must be identical.

Valid Usage

  • If the logic operations feature is not enabled, logicOpEnable must be VK_FALSE
  • If logicOpEnable is VK_TRUE, logicOp must be a valid VkLogicOp value

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_STATE_CREATE_INFO
  • pNext must be NULL or a pointer to a valid instance of VkPipelineColorBlendAdvancedStateCreateInfoEXT
  • flags must be 0
  • If attachmentCount is not 0, pAttachments must be a valid pointer to an array of attachmentCount valid VkPipelineColorBlendAttachmentState structures

See Also

VkBool32, VkGraphicsPipelineCreateInfo, VkLogicOp, VkPipelineColorBlendAttachmentState, VkPipelineColorBlendStateCreateFlags, VkStructureType

Constructors

VkPipelineColorBlendStateCreateInfo 

Fields

data VkPipelineDynamicStateCreateInfo Source #

VkPipelineDynamicStateCreateInfo - Structure specifying parameters of a newly created pipeline dynamic state

Valid Usage

  • Each element of pDynamicStates must be unique

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_DYNAMIC_STATE_CREATE_INFO
  • pNext must be NULL
  • flags must be 0
  • pDynamicStates must be a valid pointer to an array of dynamicStateCount valid VkDynamicState values
  • dynamicStateCount must be greater than 0

See Also

VkDynamicState, VkGraphicsPipelineCreateInfo, VkPipelineDynamicStateCreateFlags, VkStructureType

Constructors

VkPipelineDynamicStateCreateInfo 

Fields

data VkStencilOpState Source #

VkStencilOpState - Structure specifying stencil operation state

Valid Usage (Implicit)

See Also

VkCompareOp, VkPipelineDepthStencilStateCreateInfo, VkStencilOp

Constructors

VkStencilOpState 

Fields

  • vkFailOp :: VkStencilOp

    failOp is a VkStencilOp value specifying the action performed on samples that fail the stencil test.

  • vkPassOp :: VkStencilOp

    passOp is a VkStencilOp value specifying the action performed on samples that pass both the depth and stencil tests.

  • vkDepthFailOp :: VkStencilOp

    depthFailOp is a VkStencilOp value specifying the action performed on samples that pass the stencil test and fail the depth test.

  • vkCompareOp :: VkCompareOp

    compareOp is a VkCompareOp value specifying the comparison operator used in the stencil test.

  • vkCompareMask :: Word32

    compareMask selects the bits of the unsigned integer stencil values participating in the stencil test.

  • vkWriteMask :: Word32

    writeMask selects the bits of the unsigned integer stencil values updated by the stencil test in the stencil framebuffer attachment.

  • vkReference :: Word32

    reference is an integer reference value that is used in the unsigned stencil comparison.

data VkPipelineDepthStencilStateCreateInfo Source #

VkPipelineDepthStencilStateCreateInfo - Structure specifying parameters of a newly created pipeline depth stencil state

Valid Usage

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_PIPELINE_DEPTH_STENCIL_STATE_CREATE_INFO
  • pNext must be NULL
  • flags must be 0
  • depthCompareOp must be a valid VkCompareOp value
  • front must be a valid VkStencilOpState structure
  • back must be a valid VkStencilOpState structure

See Also

VkBool32, VkCompareOp, VkGraphicsPipelineCreateInfo, VkPipelineDepthStencilStateCreateFlags, VkStencilOpState, VkStructureType

Constructors

VkPipelineDepthStencilStateCreateInfo 

Fields

data VkGraphicsPipelineCreateInfo Source #

VkGraphicsPipelineCreateInfo - Structure specifying parameters of a newly created graphics pipeline

Description

The parameters basePipelineHandle and basePipelineIndex are described in more detail in Pipeline Derivatives.

pStages points to an array of VkPipelineShaderStageCreateInfo structures, which were previously described in Compute Pipelines.

pDynamicState points to a structure of type VkPipelineDynamicStateCreateInfo.

If any shader stage fails to compile, the compile log will be reported back to the application, and VK_ERROR_INVALID_SHADER_NV will be generated.

Valid Usage

  • If flags contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and basePipelineIndex is -1, basePipelineHandle must be a valid handle to a graphics VkPipeline
  • If flags contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and basePipelineHandle is VK_NULL_HANDLE, basePipelineIndex must be a valid index into the calling command’s pCreateInfos parameter
  • If flags contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and basePipelineIndex is not -1, basePipelineHandle must be VK_NULL_HANDLE
  • If flags contains the VK_PIPELINE_CREATE_DERIVATIVE_BIT flag, and basePipelineHandle is not VK_NULL_HANDLE, basePipelineIndex must be -1
  • The stage member of each element of pStages must be unique
  • The stage member of one element of pStages must be VK_SHADER_STAGE_VERTEX_BIT
  • The stage member of each element of pStages must not be VK_SHADER_STAGE_COMPUTE_BIT
  • If pStages includes a tessellation control shader stage, it must include a tessellation evaluation shader stage
  • If pStages includes a tessellation evaluation shader stage, it must include a tessellation control shader stage
  • If pStages includes a tessellation control shader stage and a tessellation evaluation shader stage, pTessellationState must be a valid pointer to a valid VkPipelineTessellationStateCreateInfo structure
  • If pStages includes tessellation shader stages, the shader code of at least one stage must contain an OpExecutionMode instruction that specifies the type of subdivision in the pipeline
  • If pStages includes tessellation shader stages, and the shader code of both stages contain an OpExecutionMode instruction that specifies the type of subdivision in the pipeline, they must both specify the same subdivision mode
  • If pStages includes tessellation shader stages, the shader code of at least one stage must contain an OpExecutionMode instruction that specifies the output patch size in the pipeline
  • If pStages includes tessellation shader stages, and the shader code of both contain an OpExecutionMode instruction that specifies the out patch size in the pipeline, they must both specify the same patch size
  • If pStages includes tessellation shader stages, the topology member of pInputAssembly must be VK_PRIMITIVE_TOPOLOGY_PATCH_LIST
  • If the topology member of pInputAssembly is VK_PRIMITIVE_TOPOLOGY_PATCH_LIST, pStages must include tessellation shader stages
  • If pStages includes a geometry shader stage, and does not include any tessellation shader stages, its shader code must contain an OpExecutionMode instruction that specifies an input primitive type that is compatible with the primitive topology specified in pInputAssembly
  • If pStages includes a geometry shader stage, and also includes tessellation shader stages, its shader code must contain an OpExecutionMode instruction that specifies an input primitive type that is compatible with the primitive topology that is output by the tessellation stages
  • If pStages includes a fragment shader stage and a geometry shader stage, and the fragment shader code reads from an input variable that is decorated with PrimitiveID, then the geometry shader code must write to a matching output variable, decorated with PrimitiveID, in all execution paths
  • If pStages includes a fragment shader stage, its shader code must not read from any input attachment that is defined as VK_ATTACHMENT_UNUSED in subpass
  • The shader code for the entry points identified by pStages, and the rest of the state identified by this structure must adhere to the pipeline linking rules described in the Shader Interfaces chapter
  • If rasterization is not disabled and subpass uses a depth/stencil attachment in renderPass that has a layout of VK_IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL or VK_IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL in the VkAttachmentReference defined by subpass, the depthWriteEnable member of pDepthStencilState must be VK_FALSE
  • If rasterization is not disabled and subpass uses a depth/stencil attachment in renderPass that has a layout of VK_IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL or VK_IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL in the VkAttachmentReference defined by subpass, the failOp, passOp and depthFailOp members of each of the front and back members of pDepthStencilState must be VK_STENCIL_OP_KEEP
  • If rasterization is not disabled and the subpass uses color attachments, then for each color attachment in the subpass the blendEnable member of the corresponding element of the pAttachment member of pColorBlendState must be VK_FALSE if the format of the attachment does not support color blend operations, as specified by the VK_FORMAT_FEATURE_COLOR_ATTACHMENT_BLEND_BIT flag in VkFormatProperties::linearTilingFeatures or VkFormatProperties::optimalTilingFeatures returned by vkGetPhysicalDeviceFormatProperties
  • If rasterization is not disabled and the subpass uses color attachments, the attachmentCount member of pColorBlendState must be equal to the colorAttachmentCount used to create subpass
  • If no element of the pDynamicStates member of pDynamicState is VK_DYNAMIC_STATE_VIEWPORT, the pViewports member of pViewportState must be a valid pointer to an array of pViewportState::viewportCount VkViewport structures
  • If no element of the pDynamicStates member of pDynamicState is VK_DYNAMIC_STATE_SCISSOR, the pScissors member of pViewportState must be a valid pointer to an array of pViewportState::scissorCount VkRect2D structures
  • If the wide lines feature is not enabled, and no element of the pDynamicStates member of pDynamicState is VK_DYNAMIC_STATE_LINE_WIDTH, the lineWidth member of pRasterizationState must be 1.0
  • If the rasterizerDiscardEnable member of pRasterizationState is VK_FALSE, pViewportState must be a valid pointer to a valid VkPipelineViewportStateCreateInfo structure
  • If the rasterizerDiscardEnable member of pRasterizationState is VK_FALSE, pMultisampleState must be a valid pointer to a valid VkPipelineMultisampleStateCreateInfo structure
  • If the rasterizerDiscardEnable member of pRasterizationState is VK_FALSE, and subpass uses a depth/stencil attachment, pDepthStencilState must be a valid pointer to a valid VkPipelineDepthStencilStateCreateInfo structure
  • If the rasterizerDiscardEnable member of pRasterizationState is VK_FALSE, and subpass uses color attachments, pColorBlendState must be a valid pointer to a valid VkPipelineColorBlendStateCreateInfo structure
  • If the depth bias clamping feature is not enabled, no element of the pDynamicStates member of pDynamicState is VK_DYNAMIC_STATE_DEPTH_BIAS, and the depthBiasEnable member of pRasterizationState is VK_TRUE, the depthBiasClamp member of pRasterizationState must be 0.0
  • If the {html_spec_relative}#VK_EXT_depth_range_unrestricted extension is not enabled and no element of the pDynamicStates member of pDynamicState is VK_DYNAMIC_STATE_DEPTH_BOUNDS, and the depthBoundsTestEnable member of pDepthStencilState is VK_TRUE, the minDepthBounds and maxDepthBounds members of pDepthStencilState must be between 0.0 and 1.0, inclusive
  • If no element of the pDynamicStates member of pDynamicState is VK_DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT, and the sampleLocationsEnable member of a VkPipelineSampleLocationsStateCreateInfoEXT structure chained to the pNext chain of pMultisampleState is VK_TRUE, sampleLocationsInfo.sampleLocationGridSize.width must evenly divide VkMultisamplePropertiesEXT::sampleLocationGridSize.width as returned by vkGetPhysicalDeviceMultisamplePropertiesEXT with a samples parameter equaling rasterizationSamples
  • If no element of the pDynamicStates member of pDynamicState is VK_DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT, and the sampleLocationsEnable member of a VkPipelineSampleLocationsStateCreateInfoEXT structure chained to the pNext chain of pMultisampleState is VK_TRUE, sampleLocationsInfo.sampleLocationGridSize.height must evenly divide VkMultisamplePropertiesEXT::sampleLocationGridSize.height as returned by vkGetPhysicalDeviceMultisamplePropertiesEXT with a samples parameter equaling rasterizationSamples
  • If no element of the pDynamicStates member of pDynamicState is VK_DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT, and the sampleLocationsEnable member of a VkPipelineSampleLocationsStateCreateInfoEXT structure chained to the pNext chain of pMultisampleState is VK_TRUE, sampleLocationsInfo.sampleLocationsPerPixel must equal rasterizationSamples
  • If the sampleLocationsEnable member of a VkPipelineSampleLocationsStateCreateInfoEXT structure chained to the pNext chain of pMultisampleState is VK_TRUE, the fragment shader code must not statically use the extended instruction InterpolateAtSample
  • layout must be consistent with all shaders specified in pStages
  • If subpass uses color and/or depth/stencil attachments, then the rasterizationSamples member of pMultisampleState must equal the maximum of the sample counts of those subpass attachments
  • If subpass has a depth/stencil attachment and depth test, stencil test, or depth bounds test are enabled, then the rasterizationSamples member of pMultisampleState must be the same as the sample count of the depth/stencil attachment
  • If subpass has any color attachments, then the rasterizationSamples member of pMultisampleState must be greater than or equal to the sample count for those subpass attachments
  • If subpass does not use any color and/or depth/stencil attachments, then the rasterizationSamples member of pMultisampleState must follow the rules for a zero-attachment subpass
  • subpass must be a valid subpass within renderPass
  • If the renderPass has multiview enabled and subpass has more than one bit set in the view mask and multiviewTessellationShader is not enabled, then pStages must not include tessellation shaders.
  • If the renderPass has multiview enabled and subpass has more than one bit set in the view mask and multiviewGeometryShader is not enabled, then pStages must not include a geometry shader.
  • If the renderPass has multiview enabled and subpass has more than one bit set in the view mask, shaders in the pipeline must not write to the Layer built-in output
  • If the renderPass has multiview enabled, then all shaders must not include variables decorated with the Layer built-in decoration in their interfaces.
  • flags must not contain the VK_PIPELINE_CREATE_DISPATCH_BASE flag.
  • If pStages includes a fragment shader stage and an input attachment was referenced by the VkRenderPassInputAttachmentAspectCreateInfo at renderPass create time, its shader code must not read from any aspect that was not specified in the aspectMask of the corresponding VkInputAttachmentAspectReference structure.
  • The number of resources in layout accessible to each shader stage that is used by the pipeline must be less than or equal to VkPhysicalDeviceLimits::maxPerStageResources
  • If no element of the pDynamicStates member of pDynamicState is VK_DYNAMIC_STATE_VIEWPORT_W_SCALING_NV, and the viewportWScalingEnable member of a VkPipelineViewportWScalingStateCreateInfoNV structure, chained to the pNext chain of pViewportState, is VK_TRUE, the pViewportWScalings member of the VkPipelineViewportWScalingStateCreateInfoNV must be a pointer to an array of VkPipelineViewportWScalingStateCreateInfoNV::viewportCount valid VkViewportWScalingNV structures

Valid Usage (Implicit)

  • sType must be VK_STRUCTURE_TYPE_GRAPHICS_PIPELINE_CREATE_INFO
  • pNext must be NULL or a pointer to a valid instance of VkPipelineDiscardRectangleStateCreateInfoEXT
  • flags must be a valid combination of VkPipelineCreateFlagBits values
  • pStages must be a valid pointer to an array of stageCount valid VkPipelineShaderStageCreateInfo structures
  • pVertexInputState must be a valid pointer to a valid VkPipelineVertexInputStateCreateInfo structure
  • pInputAssemblyState must be a valid pointer to a valid VkPipelineInputAssemblyStateCreateInfo structure
  • pRasterizationState must be a valid pointer to a valid VkPipelineRasterizationStateCreateInfo structure
  • If pDynamicState is not NULL, pDynamicState must be a valid pointer to a valid VkPipelineDynamicStateCreateInfo structure
  • layout must be a valid VkPipelineLayout handle
  • renderPass must be a valid VkRenderPass handle
  • stageCount must be greater than 0
  • Each of basePipelineHandle, layout, and renderPass that are valid handles must have been created, allocated, or retrieved from the same VkDevice

See Also

VkPipeline, VkPipelineColorBlendStateCreateInfo, VkPipelineCreateFlags, VkPipelineDepthStencilStateCreateInfo, VkPipelineDynamicStateCreateInfo, VkPipelineInputAssemblyStateCreateInfo, VkPipelineLayout, VkPipelineMultisampleStateCreateInfo, VkPipelineRasterizationStateCreateInfo, VkPipelineShaderStageCreateInfo, VkPipelineTessellationStateCreateInfo, VkPipelineVertexInputStateCreateInfo, VkPipelineViewportStateCreateInfo, VkRenderPass, VkStructureType, vkCreateGraphicsPipelines

Constructors

VkGraphicsPipelineCreateInfo 

Fields

type VkPipelineCreateFlags = VkPipelineCreateFlagBits Source #

VkPipelineCreateFlags - Bitmask of VkPipelineCreateFlagBits

Description

VkPipelineCreateFlags is a bitmask type for setting a mask of zero or more VkPipelineCreateFlagBits.

See Also

VkComputePipelineCreateInfo, VkGraphicsPipelineCreateInfo, VkPipelineCreateFlagBits

type VkColorComponentFlags = VkColorComponentFlagBits Source #

VkColorComponentFlags - Bitmask of VkColorComponentFlagBits

Description

VkColorComponentFlags is a bitmask type for setting a mask of zero or more VkColorComponentFlagBits.

See Also

VkColorComponentFlagBits, VkPipelineColorBlendAttachmentState

type VkCullModeFlags = VkCullModeFlagBits Source #

VkCullModeFlags - Bitmask of VkCullModeFlagBits

Description

VkCullModeFlags is a bitmask type for setting a mask of zero or more VkCullModeFlagBits.

See Also

VkCullModeFlagBits, VkPipelineRasterizationStateCreateInfo

type VkSampleMask = Word32 Source #

VkSampleMask - Mask of sample coverage information

See Also

VkPipelineMultisampleStateCreateInfo