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

Vulkan.Core10.Pipeline

Synopsis

Documentation

createGraphicsPipelines Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that creates the graphics pipelines.

-> PipelineCache

pipelineCache is either 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.

-> ("createInfos" ::: Vector (SomeStruct GraphicsPipelineCreateInfo))

pCreateInfos is a pointer to an array of GraphicsPipelineCreateInfo structures.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io (Result, "pipelines" ::: Vector Pipeline) 

vkCreateGraphicsPipelines - Create graphics pipelines

Description

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

Note

An implicit cache may be provided by the implementation or a layer. For this reason, it is still valid to set PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT on flags for any element of pCreateInfos while passing NULL_HANDLE for pipelineCache.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If pipelineCache is not NULL_HANDLE, pipelineCache must be a valid PipelineCache handle
  • pCreateInfos must be a valid pointer to an array of createInfoCount valid GraphicsPipelineCreateInfo structures
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • pPipelines must be a valid pointer to an array of createInfoCount Pipeline 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
Failure

See Also

AllocationCallbacks, Device, GraphicsPipelineCreateInfo, Pipeline, PipelineCache

withGraphicsPipelines :: forall io r. MonadIO io => Device -> PipelineCache -> Vector (SomeStruct GraphicsPipelineCreateInfo) -> Maybe AllocationCallbacks -> (io (Result, Vector Pipeline) -> ((Result, Vector Pipeline) -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createGraphicsPipelines and destroyPipeline

To ensure that destroyPipeline is always called: pass bracket (or the allocate function from your favourite resource management library) as the first argument. To just extract the pair pass (,) as the first argument.

createComputePipelines Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that creates the compute pipelines.

-> PipelineCache

pipelineCache is either 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.

-> ("createInfos" ::: Vector (SomeStruct ComputePipelineCreateInfo))

pCreateInfos is a pointer to an array of ComputePipelineCreateInfo structures.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io (Result, "pipelines" ::: Vector Pipeline) 

vkCreateComputePipelines - Creates a new compute pipeline object

Valid Usage

  • If the flags member of any element of pCreateInfos contains the 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

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If pipelineCache is not NULL_HANDLE, pipelineCache must be a valid PipelineCache handle
  • pCreateInfos must be a valid pointer to an array of createInfoCount valid ComputePipelineCreateInfo structures
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • pPipelines must be a valid pointer to an array of createInfoCount Pipeline 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
Failure

See Also

AllocationCallbacks, ComputePipelineCreateInfo, Device, Pipeline, PipelineCache

withComputePipelines :: forall io r. MonadIO io => Device -> PipelineCache -> Vector (SomeStruct ComputePipelineCreateInfo) -> Maybe AllocationCallbacks -> (io (Result, Vector Pipeline) -> ((Result, Vector Pipeline) -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createComputePipelines and destroyPipeline

To ensure that destroyPipeline is always called: pass bracket (or the allocate function from your favourite resource management library) as the first argument. To just extract the pair pass (,) as the first argument.

destroyPipeline Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the pipeline.

-> Pipeline

pipeline is the handle of the pipeline to destroy.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io () 

vkDestroyPipeline - Destroy a pipeline object

Valid Usage

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

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If pipeline is not NULL_HANDLE, pipeline must be a valid Pipeline handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks 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

AllocationCallbacks, Device, Pipeline

data Viewport 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.

If a render pass transform is enabled, the values (px,py) and (ox, oy) defining the viewport are transformed as described in render pass transform before participating in the viewport transform.

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 PhysicalDeviceLimits::maxViewportDimensions[0]
  • The absolute value of height must be less than or equal to PhysicalDeviceLimits::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 VK_EXT_depth_range_unrestricted extension is enabled minDepth must be between 0.0 and 1.0, inclusive
  • Unless VK_EXT_depth_range_unrestricted extension is enabled maxDepth must be between 0.0 and 1.0, inclusive

See Also

PipelineViewportStateCreateInfo, cmdSetViewport, cmdSetViewportWithCountEXT

Constructors

Viewport 

Fields

  • x :: Float

    x and y are the viewport’s upper left corner (x,y).

  • y :: Float
     
  • width :: Float

    width and height are the viewport’s width and height, respectively.

  • height :: Float
     
  • minDepth :: Float

    minDepth and maxDepth are the depth range for the viewport. It is valid for minDepth to be greater than or equal to maxDepth.

  • maxDepth :: Float
     

Instances

Instances details
Eq Viewport Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show Viewport Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic Viewport Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep Viewport :: Type -> Type #

Methods

from :: Viewport -> Rep Viewport x #

to :: Rep Viewport x -> Viewport #

Storable Viewport Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

FromCStruct Viewport Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct Viewport Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero Viewport Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Methods

zero :: Viewport Source #

type Rep Viewport Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

data SpecializationMapEntry 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 Bool32

See Also

SpecializationInfo

Constructors

SpecializationMapEntry 

Fields

  • constantID :: Word32

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

  • offset :: Word32

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

  • size :: Word64

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

Instances

Instances details
Eq SpecializationMapEntry Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show SpecializationMapEntry Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic SpecializationMapEntry Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep SpecializationMapEntry :: Type -> Type #

Storable SpecializationMapEntry Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

FromCStruct SpecializationMapEntry Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct SpecializationMapEntry Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero SpecializationMapEntry Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep SpecializationMapEntry Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep SpecializationMapEntry = D1 ('MetaData "SpecializationMapEntry" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "SpecializationMapEntry" 'PrefixI 'True) (S1 ('MetaSel ('Just "constantID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "offset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word64))))

data SpecializationInfo Source #

VkSpecializationInfo - Structure specifying specialization info

Description

pMapEntries is a pointer to a SpecializationMapEntry structure.

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

Valid Usage (Implicit)

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

See Also

PipelineShaderStageCreateInfo, SpecializationMapEntry

Constructors

SpecializationInfo 

Fields

Instances

Instances details
Show SpecializationInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic SpecializationInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep SpecializationInfo :: Type -> Type #

FromCStruct SpecializationInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct SpecializationInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero SpecializationInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep SpecializationInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep SpecializationInfo = D1 ('MetaData "SpecializationInfo" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "SpecializationInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "mapEntries") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector SpecializationMapEntry)) :*: (S1 ('MetaSel ('Just "dataSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "data'") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Ptr ())))))

data PipelineShaderStageCreateInfo (es :: [Type]) Source #

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

Valid Usage

Valid Usage (Implicit)

See Also

ComputePipelineCreateInfo, GraphicsPipelineCreateInfo, GraphicsShaderGroupCreateInfoNV, PipelineShaderStageCreateFlags, RayTracingPipelineCreateInfoKHR, RayTracingPipelineCreateInfoNV, ShaderModule, ShaderStageFlagBits, SpecializationInfo, StructureType

Constructors

PipelineShaderStageCreateInfo 

Fields

Instances

Instances details
Extensible PipelineShaderStageCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Methods

extensibleType :: StructureType Source #

getNext :: forall (es :: [Type]). PipelineShaderStageCreateInfo es -> Chain es Source #

setNext :: forall (ds :: [Type]) (es :: [Type]). PipelineShaderStageCreateInfo ds -> Chain es -> PipelineShaderStageCreateInfo es Source #

extends :: forall e b proxy. Typeable e => proxy e -> (Extends PipelineShaderStageCreateInfo e => b) -> Maybe b Source #

Show (Chain es) => Show (PipelineShaderStageCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic (PipelineShaderStageCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep (PipelineShaderStageCreateInfo es) :: Type -> Type #

(Extendss PipelineShaderStageCreateInfo es, PeekChain es) => FromCStruct (PipelineShaderStageCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

(Extendss PipelineShaderStageCreateInfo es, PokeChain es) => ToCStruct (PipelineShaderStageCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

es ~ ('[] :: [Type]) => Zero (PipelineShaderStageCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineShaderStageCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

data ComputePipelineCreateInfo (es :: [Type]) 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.

Valid Usage

Valid Usage (Implicit)

See Also

Pipeline, PipelineCreateFlags, PipelineLayout, PipelineShaderStageCreateInfo, StructureType, createComputePipelines

Constructors

ComputePipelineCreateInfo 

Fields

Instances

Instances details
Extensible ComputePipelineCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Methods

extensibleType :: StructureType Source #

getNext :: forall (es :: [Type]). ComputePipelineCreateInfo es -> Chain es Source #

setNext :: forall (ds :: [Type]) (es :: [Type]). ComputePipelineCreateInfo ds -> Chain es -> ComputePipelineCreateInfo es Source #

extends :: forall e b proxy. Typeable e => proxy e -> (Extends ComputePipelineCreateInfo e => b) -> Maybe b Source #

Show (Chain es) => Show (ComputePipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic (ComputePipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep (ComputePipelineCreateInfo es) :: Type -> Type #

(Extendss ComputePipelineCreateInfo es, PeekChain es) => FromCStruct (ComputePipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

(Extendss ComputePipelineCreateInfo es, PokeChain es) => ToCStruct (ComputePipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

es ~ ('[] :: [Type]) => Zero (ComputePipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (ComputePipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

data VertexInputBindingDescription Source #

VkVertexInputBindingDescription - Structure specifying vertex input binding description

Valid Usage (Implicit)

See Also

PipelineVertexInputStateCreateInfo, VertexInputRate

Constructors

VertexInputBindingDescription 

Fields

Instances

Instances details
Eq VertexInputBindingDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show VertexInputBindingDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic VertexInputBindingDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep VertexInputBindingDescription :: Type -> Type #

Storable VertexInputBindingDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

FromCStruct VertexInputBindingDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct VertexInputBindingDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero VertexInputBindingDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep VertexInputBindingDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep VertexInputBindingDescription = D1 ('MetaData "VertexInputBindingDescription" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "VertexInputBindingDescription" 'PrefixI 'True) (S1 ('MetaSel ('Just "binding") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "stride") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "inputRate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 VertexInputRate))))

data VertexInputAttributeDescription Source #

VkVertexInputAttributeDescription - Structure specifying vertex input attribute description

Valid Usage (Implicit)

See Also

Format, PipelineVertexInputStateCreateInfo

Constructors

VertexInputAttributeDescription 

Fields

Instances

Instances details
Eq VertexInputAttributeDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show VertexInputAttributeDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic VertexInputAttributeDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep VertexInputAttributeDescription :: Type -> Type #

Storable VertexInputAttributeDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

FromCStruct VertexInputAttributeDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct VertexInputAttributeDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero VertexInputAttributeDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep VertexInputAttributeDescription Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep VertexInputAttributeDescription = D1 ('MetaData "VertexInputAttributeDescription" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "VertexInputAttributeDescription" 'PrefixI 'True) ((S1 ('MetaSel ('Just "location") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "binding") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "format") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Format) :*: S1 ('MetaSel ('Just "offset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32))))

data PipelineVertexInputStateCreateInfo (es :: [Type]) Source #

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

Valid Usage

  • vertexBindingDescriptionCount must be less than or equal to PhysicalDeviceLimits::maxVertexInputBindings
  • vertexAttributeDescriptionCount must be less than or equal to PhysicalDeviceLimits::maxVertexInputAttributes
  • For every binding specified by each element of pVertexAttributeDescriptions, a VertexInputBindingDescription 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)

  • pNext must be NULL or a pointer to a valid instance of PipelineVertexInputDivisorStateCreateInfoEXT
  • The sType value of each struct in the pNext chain must be unique
  • flags must be 0
  • If vertexBindingDescriptionCount is not 0, pVertexBindingDescriptions must be a valid pointer to an array of vertexBindingDescriptionCount valid VertexInputBindingDescription structures
  • If vertexAttributeDescriptionCount is not 0, pVertexAttributeDescriptions must be a valid pointer to an array of vertexAttributeDescriptionCount valid VertexInputAttributeDescription structures

See Also

GraphicsPipelineCreateInfo, GraphicsShaderGroupCreateInfoNV, PipelineVertexInputStateCreateFlags, StructureType, VertexInputAttributeDescription, VertexInputBindingDescription

Constructors

PipelineVertexInputStateCreateInfo 

Fields

Instances

Instances details
Extensible PipelineVertexInputStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show (Chain es) => Show (PipelineVertexInputStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic (PipelineVertexInputStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep (PipelineVertexInputStateCreateInfo es) :: Type -> Type #

(Extendss PipelineVertexInputStateCreateInfo es, PeekChain es) => FromCStruct (PipelineVertexInputStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

(Extendss PipelineVertexInputStateCreateInfo es, PokeChain es) => ToCStruct (PipelineVertexInputStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

es ~ ('[] :: [Type]) => Zero (PipelineVertexInputStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineVertexInputStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineVertexInputStateCreateInfo es) = D1 ('MetaData "PipelineVertexInputStateCreateInfo" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "PipelineVertexInputStateCreateInfo" 'PrefixI 'True) ((S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PipelineVertexInputStateCreateFlags)) :*: (S1 ('MetaSel ('Just "vertexBindingDescriptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector VertexInputBindingDescription)) :*: S1 ('MetaSel ('Just "vertexAttributeDescriptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector VertexInputAttributeDescription)))))

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

Valid Usage (Implicit)

See Also

Bool32, GraphicsPipelineCreateInfo, PipelineInputAssemblyStateCreateFlags, PrimitiveTopology, StructureType

Constructors

PipelineInputAssemblyStateCreateInfo 

Fields

Instances

Instances details
Eq PipelineInputAssemblyStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show PipelineInputAssemblyStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic PipelineInputAssemblyStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Storable PipelineInputAssemblyStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

FromCStruct PipelineInputAssemblyStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct PipelineInputAssemblyStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero PipelineInputAssemblyStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep PipelineInputAssemblyStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep PipelineInputAssemblyStateCreateInfo = D1 ('MetaData "PipelineInputAssemblyStateCreateInfo" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "PipelineInputAssemblyStateCreateInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PipelineInputAssemblyStateCreateFlags) :*: (S1 ('MetaSel ('Just "topology") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PrimitiveTopology) :*: S1 ('MetaSel ('Just "primitiveRestartEnable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

data PipelineTessellationStateCreateInfo (es :: [Type]) 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 PhysicalDeviceLimits::maxTessellationPatchSize

Valid Usage (Implicit)

See Also

GraphicsPipelineCreateInfo, GraphicsShaderGroupCreateInfoNV, PipelineTessellationStateCreateFlags, StructureType

Constructors

PipelineTessellationStateCreateInfo 

Fields

Instances

Instances details
Extensible PipelineTessellationStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show (Chain es) => Show (PipelineTessellationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic (PipelineTessellationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep (PipelineTessellationStateCreateInfo es) :: Type -> Type #

(Extendss PipelineTessellationStateCreateInfo es, PeekChain es) => FromCStruct (PipelineTessellationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

(Extendss PipelineTessellationStateCreateInfo es, PokeChain es) => ToCStruct (PipelineTessellationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

es ~ ('[] :: [Type]) => Zero (PipelineTessellationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineTessellationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineTessellationStateCreateInfo es) = D1 ('MetaData "PipelineTessellationStateCreateInfo" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "PipelineTessellationStateCreateInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PipelineTessellationStateCreateFlags) :*: S1 ('MetaSel ('Just "patchControlPoints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32))))

data PipelineViewportStateCreateInfo (es :: [Type]) Source #

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

Valid Usage

  • If the multiple viewports feature is not enabled, viewportCount must not be greater than 1

Valid Usage (Implicit)

See Also

GraphicsPipelineCreateInfo, PipelineViewportStateCreateFlags, Rect2D, StructureType, Viewport

Constructors

PipelineViewportStateCreateInfo 

Fields

Instances

Instances details
Extensible PipelineViewportStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show (Chain es) => Show (PipelineViewportStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic (PipelineViewportStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep (PipelineViewportStateCreateInfo es) :: Type -> Type #

(Extendss PipelineViewportStateCreateInfo es, PeekChain es) => FromCStruct (PipelineViewportStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

(Extendss PipelineViewportStateCreateInfo es, PokeChain es) => ToCStruct (PipelineViewportStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

es ~ ('[] :: [Type]) => Zero (PipelineViewportStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineViewportStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

data PipelineRasterizationStateCreateInfo (es :: [Type]) Source #

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

Description

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

Valid Usage

Valid Usage (Implicit)

See Also

Bool32, CullModeFlags, FrontFace, GraphicsPipelineCreateInfo, PipelineRasterizationStateCreateFlags, PolygonMode, StructureType

Constructors

PipelineRasterizationStateCreateInfo 

Fields

Instances

Instances details
Extensible PipelineRasterizationStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show (Chain es) => Show (PipelineRasterizationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic (PipelineRasterizationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep (PipelineRasterizationStateCreateInfo es) :: Type -> Type #

(Extendss PipelineRasterizationStateCreateInfo es, PeekChain es) => FromCStruct (PipelineRasterizationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

(Extendss PipelineRasterizationStateCreateInfo es, PokeChain es) => ToCStruct (PipelineRasterizationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

es ~ ('[] :: [Type]) => Zero (PipelineRasterizationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineRasterizationStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineRasterizationStateCreateInfo es) = D1 ('MetaData "PipelineRasterizationStateCreateInfo" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "PipelineRasterizationStateCreateInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PipelineRasterizationStateCreateFlags) :*: S1 ('MetaSel ('Just "depthClampEnable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))) :*: (S1 ('MetaSel ('Just "rasterizerDiscardEnable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "polygonMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PolygonMode) :*: S1 ('MetaSel ('Just "cullMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CullModeFlags)))) :*: ((S1 ('MetaSel ('Just "frontFace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FrontFace) :*: (S1 ('MetaSel ('Just "depthBiasEnable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "depthBiasConstantFactor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float))) :*: (S1 ('MetaSel ('Just "depthBiasClamp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float) :*: (S1 ('MetaSel ('Just "depthBiasSlopeFactor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float) :*: S1 ('MetaSel ('Just "lineWidth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Float))))))

data PipelineMultisampleStateCreateInfo (es :: [Type]) Source #

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

Description

Each bit in the sample mask is associated with a unique sample index as defined for the coverage mask. Each bit b for mask word w in the sample mask corresponds to sample index i, where i = 32 × w + b. pSampleMask has a length equal to ⌈ rasterizationSamples / 32 ⌉ words.

If pSampleMask is NULL, it is treated as if the mask has all bits set to 1.

Valid Usage

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

Valid Usage (Implicit)

See Also

Bool32, GraphicsPipelineCreateInfo, PipelineMultisampleStateCreateFlags, SampleCountFlagBits, SampleMask, StructureType

Constructors

PipelineMultisampleStateCreateInfo 

Fields

Instances

Instances details
Extensible PipelineMultisampleStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show (Chain es) => Show (PipelineMultisampleStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic (PipelineMultisampleStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep (PipelineMultisampleStateCreateInfo es) :: Type -> Type #

(Extendss PipelineMultisampleStateCreateInfo es, PeekChain es) => FromCStruct (PipelineMultisampleStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

(Extendss PipelineMultisampleStateCreateInfo es, PokeChain es) => ToCStruct (PipelineMultisampleStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

es ~ ('[] :: [Type]) => Zero (PipelineMultisampleStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineMultisampleStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

data PipelineColorBlendAttachmentState Source #

VkPipelineColorBlendAttachmentState - Structure specifying a pipeline color blend attachment state

Valid Usage

Valid Usage (Implicit)

See Also

BlendFactor, BlendOp, Bool32, ColorComponentFlags, PipelineColorBlendStateCreateInfo

Constructors

PipelineColorBlendAttachmentState 

Fields

Instances

Instances details
Eq PipelineColorBlendAttachmentState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show PipelineColorBlendAttachmentState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic PipelineColorBlendAttachmentState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep PipelineColorBlendAttachmentState :: Type -> Type #

Storable PipelineColorBlendAttachmentState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

FromCStruct PipelineColorBlendAttachmentState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct PipelineColorBlendAttachmentState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero PipelineColorBlendAttachmentState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep PipelineColorBlendAttachmentState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

data PipelineColorBlendStateCreateInfo (es :: [Type]) Source #

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

Description

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

Valid Usage

Valid Usage (Implicit)

See Also

Bool32, GraphicsPipelineCreateInfo, LogicOp, PipelineColorBlendAttachmentState, PipelineColorBlendStateCreateFlags, StructureType

Constructors

PipelineColorBlendStateCreateInfo 

Fields

Instances

Instances details
Extensible PipelineColorBlendStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show (Chain es) => Show (PipelineColorBlendStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic (PipelineColorBlendStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep (PipelineColorBlendStateCreateInfo es) :: Type -> Type #

(Extendss PipelineColorBlendStateCreateInfo es, PeekChain es) => FromCStruct (PipelineColorBlendStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

(Extendss PipelineColorBlendStateCreateInfo es, PokeChain es) => ToCStruct (PipelineColorBlendStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

es ~ ('[] :: [Type]) => Zero (PipelineColorBlendStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (PipelineColorBlendStateCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

data PipelineDynamicStateCreateInfo Source #

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

Valid Usage

  • Each element of pDynamicStates must be unique

Valid Usage (Implicit)

  • pNext must be NULL
  • flags must be 0
  • If dynamicStateCount is not 0, pDynamicStates must be a valid pointer to an array of dynamicStateCount valid DynamicState values

See Also

DynamicState, GraphicsPipelineCreateInfo, PipelineDynamicStateCreateFlags, StructureType

Constructors

PipelineDynamicStateCreateInfo 

Fields

Instances

Instances details
Show PipelineDynamicStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic PipelineDynamicStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep PipelineDynamicStateCreateInfo :: Type -> Type #

FromCStruct PipelineDynamicStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct PipelineDynamicStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero PipelineDynamicStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep PipelineDynamicStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep PipelineDynamicStateCreateInfo = D1 ('MetaData "PipelineDynamicStateCreateInfo" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "PipelineDynamicStateCreateInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PipelineDynamicStateCreateFlags) :*: S1 ('MetaSel ('Just "dynamicStates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector DynamicState))))

data StencilOpState Source #

VkStencilOpState - Structure specifying stencil operation state

Valid Usage (Implicit)

See Also

CompareOp, PipelineDepthStencilStateCreateInfo, StencilOp

Constructors

StencilOpState 

Fields

  • failOp :: StencilOp

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

    failOp must be a valid StencilOp value

  • passOp :: StencilOp

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

    passOp must be a valid StencilOp value

  • depthFailOp :: StencilOp

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

    depthFailOp must be a valid StencilOp value

  • compareOp :: CompareOp

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

    compareOp must be a valid CompareOp value

  • compareMask :: Word32

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

  • writeMask :: Word32

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

  • reference :: Word32

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

Instances

Instances details
Eq StencilOpState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Show StencilOpState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic StencilOpState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep StencilOpState :: Type -> Type #

Storable StencilOpState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

FromCStruct StencilOpState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct StencilOpState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero StencilOpState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep StencilOpState Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

data PipelineDepthStencilStateCreateInfo Source #

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

Valid Usage

Valid Usage (Implicit)

See Also

Bool32, CompareOp, GraphicsPipelineCreateInfo, PipelineDepthStencilStateCreateFlags, StencilOpState, StructureType

Constructors

PipelineDepthStencilStateCreateInfo 

Fields

Instances

Instances details
Show PipelineDepthStencilStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic PipelineDepthStencilStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

FromCStruct PipelineDepthStencilStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

ToCStruct PipelineDepthStencilStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Zero PipelineDepthStencilStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep PipelineDepthStencilStateCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

data GraphicsPipelineCreateInfo (es :: [Type]) 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.

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

Valid Usage

Valid Usage (Implicit)

See Also

Pipeline, PipelineColorBlendStateCreateInfo, PipelineCreateFlags, PipelineDepthStencilStateCreateInfo, PipelineDynamicStateCreateInfo, PipelineInputAssemblyStateCreateInfo, PipelineLayout, PipelineMultisampleStateCreateInfo, PipelineRasterizationStateCreateInfo, PipelineShaderStageCreateInfo, PipelineTessellationStateCreateInfo, PipelineVertexInputStateCreateInfo, PipelineViewportStateCreateInfo, RenderPass, StructureType, createGraphicsPipelines

Constructors

GraphicsPipelineCreateInfo 

Fields

Instances

Instances details
Extensible GraphicsPipelineCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Methods

extensibleType :: StructureType Source #

getNext :: forall (es :: [Type]). GraphicsPipelineCreateInfo es -> Chain es Source #

setNext :: forall (ds :: [Type]) (es :: [Type]). GraphicsPipelineCreateInfo ds -> Chain es -> GraphicsPipelineCreateInfo es Source #

extends :: forall e b proxy. Typeable e => proxy e -> (Extends GraphicsPipelineCreateInfo e => b) -> Maybe b Source #

Show (Chain es) => Show (GraphicsPipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Generic (GraphicsPipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

Associated Types

type Rep (GraphicsPipelineCreateInfo es) :: Type -> Type #

(Extendss GraphicsPipelineCreateInfo es, PeekChain es) => FromCStruct (GraphicsPipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

(Extendss GraphicsPipelineCreateInfo es, PokeChain es) => ToCStruct (GraphicsPipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

es ~ ('[] :: [Type]) => Zero (GraphicsPipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (GraphicsPipelineCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pipeline

type Rep (GraphicsPipelineCreateInfo es) = D1 ('MetaData "GraphicsPipelineCreateInfo" "Vulkan.Core10.Pipeline" "vulkan-3.6.3-inplace" 'False) (C1 ('MetaCons "GraphicsPipelineCreateInfo" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PipelineCreateFlags)) :*: (S1 ('MetaSel ('Just "stages") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector (SomeStruct PipelineShaderStageCreateInfo))) :*: S1 ('MetaSel ('Just "vertexInputState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (SomeStruct PipelineVertexInputStateCreateInfo))))) :*: ((S1 ('MetaSel ('Just "inputAssemblyState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PipelineInputAssemblyStateCreateInfo)) :*: S1 ('MetaSel ('Just "tessellationState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (SomeStruct PipelineTessellationStateCreateInfo)))) :*: (S1 ('MetaSel ('Just "viewportState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (SomeStruct PipelineViewportStateCreateInfo))) :*: S1 ('MetaSel ('Just "rasterizationState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (SomeStruct PipelineRasterizationStateCreateInfo))))) :*: (((S1 ('MetaSel ('Just "multisampleState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (SomeStruct PipelineMultisampleStateCreateInfo))) :*: S1 ('MetaSel ('Just "depthStencilState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PipelineDepthStencilStateCreateInfo))) :*: (S1 ('MetaSel ('Just "colorBlendState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (SomeStruct PipelineColorBlendStateCreateInfo))) :*: S1 ('MetaSel ('Just "dynamicState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe PipelineDynamicStateCreateInfo)))) :*: ((S1 ('MetaSel ('Just "layout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PipelineLayout) :*: S1 ('MetaSel ('Just "renderPass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 RenderPass)) :*: (S1 ('MetaSel ('Just "subpass") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "basePipelineHandle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Pipeline) :*: S1 ('MetaSel ('Just "basePipelineIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int32)))))))

newtype Pipeline Source #

Constructors

Pipeline Word64 

Instances

Instances details
Eq Pipeline Source # 
Instance details

Defined in Vulkan.Core10.Handles

Ord Pipeline Source # 
Instance details

Defined in Vulkan.Core10.Handles

Show Pipeline Source # 
Instance details

Defined in Vulkan.Core10.Handles

Storable Pipeline Source # 
Instance details

Defined in Vulkan.Core10.Handles

Zero Pipeline Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

zero :: Pipeline Source #

HasObjectType Pipeline Source # 
Instance details

Defined in Vulkan.Core10.Handles

IsHandle Pipeline Source # 
Instance details

Defined in Vulkan.Core10.Handles

newtype PipelineLayoutCreateFlags Source #

VkPipelineLayoutCreateFlags - Reserved for future use

Description

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

See Also

PipelineLayoutCreateInfo

Instances

Instances details
Eq PipelineLayoutCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineLayoutCreateFlags

Ord PipelineLayoutCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineLayoutCreateFlags

Read PipelineLayoutCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineLayoutCreateFlags

Show PipelineLayoutCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineLayoutCreateFlags

Storable PipelineLayoutCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineLayoutCreateFlags

Bits PipelineLayoutCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineLayoutCreateFlags

Methods

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

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

xor :: PipelineLayoutCreateFlags -> PipelineLayoutCreateFlags -> PipelineLayoutCreateFlags #

complement :: PipelineLayoutCreateFlags -> PipelineLayoutCreateFlags #

shift :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

rotate :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

zeroBits :: PipelineLayoutCreateFlags #

bit :: Int -> PipelineLayoutCreateFlags #

setBit :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

clearBit :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

complementBit :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

testBit :: PipelineLayoutCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineLayoutCreateFlags -> Maybe Int #

bitSize :: PipelineLayoutCreateFlags -> Int #

isSigned :: PipelineLayoutCreateFlags -> Bool #

shiftL :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

unsafeShiftL :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

shiftR :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

unsafeShiftR :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

rotateL :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

rotateR :: PipelineLayoutCreateFlags -> Int -> PipelineLayoutCreateFlags #

popCount :: PipelineLayoutCreateFlags -> Int #

Zero PipelineLayoutCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineLayoutCreateFlags

newtype PipelineDepthStencilStateCreateFlags Source #

VkPipelineDepthStencilStateCreateFlags - Reserved for future use

Description

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

See Also

PipelineDepthStencilStateCreateInfo

Instances

Instances details
Eq PipelineDepthStencilStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags

Ord PipelineDepthStencilStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags

Read PipelineDepthStencilStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags

Show PipelineDepthStencilStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags

Storable PipelineDepthStencilStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags

Bits PipelineDepthStencilStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags

Methods

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

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

xor :: PipelineDepthStencilStateCreateFlags -> PipelineDepthStencilStateCreateFlags -> PipelineDepthStencilStateCreateFlags #

complement :: PipelineDepthStencilStateCreateFlags -> PipelineDepthStencilStateCreateFlags #

shift :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

rotate :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

zeroBits :: PipelineDepthStencilStateCreateFlags #

bit :: Int -> PipelineDepthStencilStateCreateFlags #

setBit :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

clearBit :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

complementBit :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

testBit :: PipelineDepthStencilStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineDepthStencilStateCreateFlags -> Maybe Int #

bitSize :: PipelineDepthStencilStateCreateFlags -> Int #

isSigned :: PipelineDepthStencilStateCreateFlags -> Bool #

shiftL :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

unsafeShiftL :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

shiftR :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

unsafeShiftR :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

rotateL :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

rotateR :: PipelineDepthStencilStateCreateFlags -> Int -> PipelineDepthStencilStateCreateFlags #

popCount :: PipelineDepthStencilStateCreateFlags -> Int #

Zero PipelineDepthStencilStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDepthStencilStateCreateFlags

newtype PipelineDynamicStateCreateFlags Source #

VkPipelineDynamicStateCreateFlags - Reserved for future use

Description

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

See Also

PipelineDynamicStateCreateInfo

Instances

Instances details
Eq PipelineDynamicStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags

Ord PipelineDynamicStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags

Read PipelineDynamicStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags

Show PipelineDynamicStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags

Storable PipelineDynamicStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags

Bits PipelineDynamicStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags

Methods

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

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

xor :: PipelineDynamicStateCreateFlags -> PipelineDynamicStateCreateFlags -> PipelineDynamicStateCreateFlags #

complement :: PipelineDynamicStateCreateFlags -> PipelineDynamicStateCreateFlags #

shift :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

rotate :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

zeroBits :: PipelineDynamicStateCreateFlags #

bit :: Int -> PipelineDynamicStateCreateFlags #

setBit :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

clearBit :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

complementBit :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

testBit :: PipelineDynamicStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineDynamicStateCreateFlags -> Maybe Int #

bitSize :: PipelineDynamicStateCreateFlags -> Int #

isSigned :: PipelineDynamicStateCreateFlags -> Bool #

shiftL :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

unsafeShiftL :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

shiftR :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

unsafeShiftR :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

rotateL :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

rotateR :: PipelineDynamicStateCreateFlags -> Int -> PipelineDynamicStateCreateFlags #

popCount :: PipelineDynamicStateCreateFlags -> Int #

Zero PipelineDynamicStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineDynamicStateCreateFlags

newtype PipelineColorBlendStateCreateFlags Source #

VkPipelineColorBlendStateCreateFlags - Reserved for future use

Description

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

See Also

PipelineColorBlendStateCreateInfo

Instances

Instances details
Eq PipelineColorBlendStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags

Ord PipelineColorBlendStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags

Read PipelineColorBlendStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags

Show PipelineColorBlendStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags

Storable PipelineColorBlendStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags

Bits PipelineColorBlendStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags

Methods

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

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

xor :: PipelineColorBlendStateCreateFlags -> PipelineColorBlendStateCreateFlags -> PipelineColorBlendStateCreateFlags #

complement :: PipelineColorBlendStateCreateFlags -> PipelineColorBlendStateCreateFlags #

shift :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

rotate :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

zeroBits :: PipelineColorBlendStateCreateFlags #

bit :: Int -> PipelineColorBlendStateCreateFlags #

setBit :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

clearBit :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

complementBit :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

testBit :: PipelineColorBlendStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineColorBlendStateCreateFlags -> Maybe Int #

bitSize :: PipelineColorBlendStateCreateFlags -> Int #

isSigned :: PipelineColorBlendStateCreateFlags -> Bool #

shiftL :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

unsafeShiftL :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

shiftR :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

unsafeShiftR :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

rotateL :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

rotateR :: PipelineColorBlendStateCreateFlags -> Int -> PipelineColorBlendStateCreateFlags #

popCount :: PipelineColorBlendStateCreateFlags -> Int #

Zero PipelineColorBlendStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineColorBlendStateCreateFlags

newtype PipelineMultisampleStateCreateFlags Source #

VkPipelineMultisampleStateCreateFlags - Reserved for future use

Description

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

See Also

PipelineMultisampleStateCreateInfo

Instances

Instances details
Eq PipelineMultisampleStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags

Ord PipelineMultisampleStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags

Read PipelineMultisampleStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags

Show PipelineMultisampleStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags

Storable PipelineMultisampleStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags

Bits PipelineMultisampleStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags

Methods

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

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

xor :: PipelineMultisampleStateCreateFlags -> PipelineMultisampleStateCreateFlags -> PipelineMultisampleStateCreateFlags #

complement :: PipelineMultisampleStateCreateFlags -> PipelineMultisampleStateCreateFlags #

shift :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

rotate :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

zeroBits :: PipelineMultisampleStateCreateFlags #

bit :: Int -> PipelineMultisampleStateCreateFlags #

setBit :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

clearBit :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

complementBit :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

testBit :: PipelineMultisampleStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineMultisampleStateCreateFlags -> Maybe Int #

bitSize :: PipelineMultisampleStateCreateFlags -> Int #

isSigned :: PipelineMultisampleStateCreateFlags -> Bool #

shiftL :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

unsafeShiftL :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

shiftR :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

unsafeShiftR :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

rotateL :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

rotateR :: PipelineMultisampleStateCreateFlags -> Int -> PipelineMultisampleStateCreateFlags #

popCount :: PipelineMultisampleStateCreateFlags -> Int #

Zero PipelineMultisampleStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineMultisampleStateCreateFlags

newtype PipelineRasterizationStateCreateFlags Source #

VkPipelineRasterizationStateCreateFlags - Reserved for future use

Description

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

See Also

PipelineRasterizationStateCreateInfo

Instances

Instances details
Eq PipelineRasterizationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags

Ord PipelineRasterizationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags

Read PipelineRasterizationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags

Show PipelineRasterizationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags

Storable PipelineRasterizationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags

Bits PipelineRasterizationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags

Methods

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

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

xor :: PipelineRasterizationStateCreateFlags -> PipelineRasterizationStateCreateFlags -> PipelineRasterizationStateCreateFlags #

complement :: PipelineRasterizationStateCreateFlags -> PipelineRasterizationStateCreateFlags #

shift :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

rotate :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

zeroBits :: PipelineRasterizationStateCreateFlags #

bit :: Int -> PipelineRasterizationStateCreateFlags #

setBit :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

clearBit :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

complementBit :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

testBit :: PipelineRasterizationStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineRasterizationStateCreateFlags -> Maybe Int #

bitSize :: PipelineRasterizationStateCreateFlags -> Int #

isSigned :: PipelineRasterizationStateCreateFlags -> Bool #

shiftL :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

unsafeShiftL :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

shiftR :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

unsafeShiftR :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

rotateL :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

rotateR :: PipelineRasterizationStateCreateFlags -> Int -> PipelineRasterizationStateCreateFlags #

popCount :: PipelineRasterizationStateCreateFlags -> Int #

Zero PipelineRasterizationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineRasterizationStateCreateFlags

newtype PipelineViewportStateCreateFlags Source #

VkPipelineViewportStateCreateFlags - Reserved for future use

Description

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

See Also

PipelineViewportStateCreateInfo

Instances

Instances details
Eq PipelineViewportStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineViewportStateCreateFlags

Ord PipelineViewportStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineViewportStateCreateFlags

Read PipelineViewportStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineViewportStateCreateFlags

Show PipelineViewportStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineViewportStateCreateFlags

Storable PipelineViewportStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineViewportStateCreateFlags

Bits PipelineViewportStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineViewportStateCreateFlags

Methods

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

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

xor :: PipelineViewportStateCreateFlags -> PipelineViewportStateCreateFlags -> PipelineViewportStateCreateFlags #

complement :: PipelineViewportStateCreateFlags -> PipelineViewportStateCreateFlags #

shift :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

rotate :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

zeroBits :: PipelineViewportStateCreateFlags #

bit :: Int -> PipelineViewportStateCreateFlags #

setBit :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

clearBit :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

complementBit :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

testBit :: PipelineViewportStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineViewportStateCreateFlags -> Maybe Int #

bitSize :: PipelineViewportStateCreateFlags -> Int #

isSigned :: PipelineViewportStateCreateFlags -> Bool #

shiftL :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

unsafeShiftL :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

shiftR :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

unsafeShiftR :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

rotateL :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

rotateR :: PipelineViewportStateCreateFlags -> Int -> PipelineViewportStateCreateFlags #

popCount :: PipelineViewportStateCreateFlags -> Int #

Zero PipelineViewportStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineViewportStateCreateFlags

newtype PipelineTessellationStateCreateFlags Source #

VkPipelineTessellationStateCreateFlags - Reserved for future use

Description

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

See Also

PipelineTessellationStateCreateInfo

Instances

Instances details
Eq PipelineTessellationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags

Ord PipelineTessellationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags

Read PipelineTessellationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags

Show PipelineTessellationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags

Storable PipelineTessellationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags

Bits PipelineTessellationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags

Methods

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

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

xor :: PipelineTessellationStateCreateFlags -> PipelineTessellationStateCreateFlags -> PipelineTessellationStateCreateFlags #

complement :: PipelineTessellationStateCreateFlags -> PipelineTessellationStateCreateFlags #

shift :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

rotate :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

zeroBits :: PipelineTessellationStateCreateFlags #

bit :: Int -> PipelineTessellationStateCreateFlags #

setBit :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

clearBit :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

complementBit :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

testBit :: PipelineTessellationStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineTessellationStateCreateFlags -> Maybe Int #

bitSize :: PipelineTessellationStateCreateFlags -> Int #

isSigned :: PipelineTessellationStateCreateFlags -> Bool #

shiftL :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

unsafeShiftL :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

shiftR :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

unsafeShiftR :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

rotateL :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

rotateR :: PipelineTessellationStateCreateFlags -> Int -> PipelineTessellationStateCreateFlags #

popCount :: PipelineTessellationStateCreateFlags -> Int #

Zero PipelineTessellationStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineTessellationStateCreateFlags

newtype PipelineInputAssemblyStateCreateFlags Source #

VkPipelineInputAssemblyStateCreateFlags - Reserved for future use

Description

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

See Also

PipelineInputAssemblyStateCreateInfo

Instances

Instances details
Eq PipelineInputAssemblyStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags

Ord PipelineInputAssemblyStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags

Read PipelineInputAssemblyStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags

Show PipelineInputAssemblyStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags

Storable PipelineInputAssemblyStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags

Bits PipelineInputAssemblyStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags

Methods

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

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

xor :: PipelineInputAssemblyStateCreateFlags -> PipelineInputAssemblyStateCreateFlags -> PipelineInputAssemblyStateCreateFlags #

complement :: PipelineInputAssemblyStateCreateFlags -> PipelineInputAssemblyStateCreateFlags #

shift :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

rotate :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

zeroBits :: PipelineInputAssemblyStateCreateFlags #

bit :: Int -> PipelineInputAssemblyStateCreateFlags #

setBit :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

clearBit :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

complementBit :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

testBit :: PipelineInputAssemblyStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineInputAssemblyStateCreateFlags -> Maybe Int #

bitSize :: PipelineInputAssemblyStateCreateFlags -> Int #

isSigned :: PipelineInputAssemblyStateCreateFlags -> Bool #

shiftL :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

unsafeShiftL :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

shiftR :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

unsafeShiftR :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

rotateL :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

rotateR :: PipelineInputAssemblyStateCreateFlags -> Int -> PipelineInputAssemblyStateCreateFlags #

popCount :: PipelineInputAssemblyStateCreateFlags -> Int #

Zero PipelineInputAssemblyStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineInputAssemblyStateCreateFlags

newtype PipelineVertexInputStateCreateFlags Source #

VkPipelineVertexInputStateCreateFlags - Reserved for future use

Description

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

See Also

PipelineVertexInputStateCreateInfo

Instances

Instances details
Eq PipelineVertexInputStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags

Ord PipelineVertexInputStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags

Read PipelineVertexInputStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags

Show PipelineVertexInputStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags

Storable PipelineVertexInputStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags

Bits PipelineVertexInputStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags

Methods

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

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

xor :: PipelineVertexInputStateCreateFlags -> PipelineVertexInputStateCreateFlags -> PipelineVertexInputStateCreateFlags #

complement :: PipelineVertexInputStateCreateFlags -> PipelineVertexInputStateCreateFlags #

shift :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

rotate :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

zeroBits :: PipelineVertexInputStateCreateFlags #

bit :: Int -> PipelineVertexInputStateCreateFlags #

setBit :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

clearBit :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

complementBit :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

testBit :: PipelineVertexInputStateCreateFlags -> Int -> Bool #

bitSizeMaybe :: PipelineVertexInputStateCreateFlags -> Maybe Int #

bitSize :: PipelineVertexInputStateCreateFlags -> Int #

isSigned :: PipelineVertexInputStateCreateFlags -> Bool #

shiftL :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

unsafeShiftL :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

shiftR :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

unsafeShiftR :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

rotateL :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

rotateR :: PipelineVertexInputStateCreateFlags -> Int -> PipelineVertexInputStateCreateFlags #

popCount :: PipelineVertexInputStateCreateFlags -> Int #

Zero PipelineVertexInputStateCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineVertexInputStateCreateFlags

newtype PrimitiveTopology Source #

VkPrimitiveTopology - Supported primitive topologies

Description

Each primitive topology, and its construction from a list of vertices, is described in detail below with a supporting diagram, according to the following key:

Vertex A point in 3-dimensional space. Positions chosen within the diagrams are arbitrary and for illustration only.
Vertex Number Sequence position of a vertex within the provided vertex data.
Provoking Vertex Provoking vertex within the main primitive. The arrow points along an edge of the relevant primitive, following winding order. Used in flat shading.
Primitive Edge An edge connecting the points of a main primitive.
Adjacency Edge Points connected by these lines do not contribute to a main primitive, and are only accessible in a geometry shader.
Winding Order The relative order in which vertices are defined within a primitive, used in the facing determination. This ordering has no specific start or end point.

The diagrams are supported with mathematical definitions where the vertices (v) and primitives (p) are numbered starting from 0; v0 is the first vertex in the provided data and p0 is the first primitive in the set of primitives defined by the vertices and topology.

See Also

PipelineInputAssemblyStateCreateInfo, cmdSetPrimitiveTopologyEXT

Constructors

PrimitiveTopology Int32 

Bundled Patterns

pattern PRIMITIVE_TOPOLOGY_POINT_LIST :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_POINT_LIST specifies a series of separate point primitives.

pattern PRIMITIVE_TOPOLOGY_LINE_LIST :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_LINE_LIST specifies a series of separate line primitives.

pattern PRIMITIVE_TOPOLOGY_LINE_STRIP :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_LINE_STRIP specifies a series of connected line primitives with consecutive lines sharing a vertex.

pattern PRIMITIVE_TOPOLOGY_TRIANGLE_LIST :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_TRIANGLE_LIST specifies a series of separate triangle primitives.

pattern PRIMITIVE_TOPOLOGY_TRIANGLE_STRIP :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_TRIANGLE_STRIP specifies a series of connected triangle primitives with consecutive triangles sharing an edge.

pattern PRIMITIVE_TOPOLOGY_TRIANGLE_FAN :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_TRIANGLE_FAN specifies a series of connected triangle primitives with all triangles sharing a common vertex.

pattern PRIMITIVE_TOPOLOGY_LINE_LIST_WITH_ADJACENCY :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_LINE_LIST_WITH_ADJACENCY specifies a series of separate line primitives with adjacency.

pattern PRIMITIVE_TOPOLOGY_LINE_STRIP_WITH_ADJACENCY :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_LINE_STRIP_WITH_ADJACENCY specifies a series of connected line primitives with adjacency, with consecutive primitives sharing three vertices.

pattern PRIMITIVE_TOPOLOGY_TRIANGLE_LIST_WITH_ADJACENCY :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_TRIANGLE_LIST_WITH_ADJACENCY specifies a series of separate triangle primitives with adjacency.

pattern PRIMITIVE_TOPOLOGY_TRIANGLE_STRIP_WITH_ADJACENCY :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_TRIANGLE_STRIP_WITH_ADJACENCY specifies connected triangle primitives with adjacency, with consecutive triangles sharing an edge.

pattern PRIMITIVE_TOPOLOGY_PATCH_LIST :: PrimitiveTopology

PRIMITIVE_TOPOLOGY_PATCH_LIST specifies separate patch primitives.

Instances

Instances details
Eq PrimitiveTopology Source # 
Instance details

Defined in Vulkan.Core10.Enums.PrimitiveTopology

Ord PrimitiveTopology Source # 
Instance details

Defined in Vulkan.Core10.Enums.PrimitiveTopology

Read PrimitiveTopology Source # 
Instance details

Defined in Vulkan.Core10.Enums.PrimitiveTopology

Show PrimitiveTopology Source # 
Instance details

Defined in Vulkan.Core10.Enums.PrimitiveTopology

Storable PrimitiveTopology Source # 
Instance details

Defined in Vulkan.Core10.Enums.PrimitiveTopology

Zero PrimitiveTopology Source # 
Instance details

Defined in Vulkan.Core10.Enums.PrimitiveTopology

newtype CompareOp Source #

Constructors

CompareOp Int32 

Bundled Patterns

pattern COMPARE_OP_NEVER :: CompareOp

COMPARE_OP_NEVER specifies that the test evaluates to false.

pattern COMPARE_OP_LESS :: CompareOp

COMPARE_OP_LESS specifies that the test evaluates A < B.

pattern COMPARE_OP_EQUAL :: CompareOp

COMPARE_OP_EQUAL specifies that the test evaluates A = B.

pattern COMPARE_OP_LESS_OR_EQUAL :: CompareOp

COMPARE_OP_LESS_OR_EQUAL specifies that the test evaluates A ≤ B.

pattern COMPARE_OP_GREATER :: CompareOp

COMPARE_OP_GREATER specifies that the test evaluates A > B.

pattern COMPARE_OP_NOT_EQUAL :: CompareOp

COMPARE_OP_NOT_EQUAL specifies that the test evaluates A ≠ B.

pattern COMPARE_OP_GREATER_OR_EQUAL :: CompareOp

COMPARE_OP_GREATER_OR_EQUAL specifies that the test evaluates A ≥ B.

pattern COMPARE_OP_ALWAYS :: CompareOp

COMPARE_OP_ALWAYS specifies that the test evaluates to true.

Instances

Instances details
Eq CompareOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.CompareOp

Ord CompareOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.CompareOp

Read CompareOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.CompareOp

Show CompareOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.CompareOp

Storable CompareOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.CompareOp

Zero CompareOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.CompareOp

newtype PolygonMode Source #

VkPolygonMode - Control polygon rasterization mode

Description

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

PipelineRasterizationStateCreateInfo

Constructors

PolygonMode Int32 

Bundled Patterns

pattern POLYGON_MODE_FILL :: PolygonMode

POLYGON_MODE_FILL specifies that polygons are rendered using the polygon rasterization rules in this section.

pattern POLYGON_MODE_LINE :: PolygonMode

POLYGON_MODE_LINE specifies that polygon edges are drawn as line segments.

pattern POLYGON_MODE_POINT :: PolygonMode

POLYGON_MODE_POINT specifies that polygon vertices are drawn as points.

pattern POLYGON_MODE_FILL_RECTANGLE_NV :: PolygonMode

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 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 POLYGON_MODE_FILL_RECTANGLE_NV mode using the triangle’s vertices.

Instances

Instances details
Eq PolygonMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.PolygonMode

Ord PolygonMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.PolygonMode

Read PolygonMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.PolygonMode

Show PolygonMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.PolygonMode

Storable PolygonMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.PolygonMode

Zero PolygonMode Source # 
Instance details

Defined in Vulkan.Core10.Enums.PolygonMode

newtype CullModeFlagBits Source #

VkCullModeFlagBits - Bitmask controlling triangle culling

Description

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

See Also

CullModeFlags

Constructors

CullModeFlagBits Flags 

Bundled Patterns

pattern CULL_MODE_NONE :: CullModeFlagBits

CULL_MODE_NONE specifies that no triangles are discarded

pattern CULL_MODE_FRONT_BIT :: CullModeFlagBits

CULL_MODE_FRONT_BIT specifies that front-facing triangles are discarded

pattern CULL_MODE_BACK_BIT :: CullModeFlagBits

CULL_MODE_BACK_BIT specifies that back-facing triangles are discarded

pattern CULL_MODE_FRONT_AND_BACK :: CullModeFlagBits

CULL_MODE_FRONT_AND_BACK specifies that all triangles are discarded.

Instances

Instances details
Eq CullModeFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.CullModeFlagBits

Ord CullModeFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.CullModeFlagBits

Read CullModeFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.CullModeFlagBits

Show CullModeFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.CullModeFlagBits

Storable CullModeFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.CullModeFlagBits

Bits CullModeFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.CullModeFlagBits

Zero CullModeFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.CullModeFlagBits

newtype FrontFace Source #

VkFrontFace - Interpret polygon front-facing orientation

Description

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

See Also

PipelineRasterizationStateCreateInfo, cmdSetFrontFaceEXT

Constructors

FrontFace Int32 

Bundled Patterns

pattern FRONT_FACE_COUNTER_CLOCKWISE :: FrontFace

FRONT_FACE_COUNTER_CLOCKWISE specifies that a triangle with positive area is considered front-facing.

pattern FRONT_FACE_CLOCKWISE :: FrontFace

FRONT_FACE_CLOCKWISE specifies that a triangle with negative area is considered front-facing.

Instances

Instances details
Eq FrontFace Source # 
Instance details

Defined in Vulkan.Core10.Enums.FrontFace

Ord FrontFace Source # 
Instance details

Defined in Vulkan.Core10.Enums.FrontFace

Read FrontFace Source # 
Instance details

Defined in Vulkan.Core10.Enums.FrontFace

Show FrontFace Source # 
Instance details

Defined in Vulkan.Core10.Enums.FrontFace

Storable FrontFace Source # 
Instance details

Defined in Vulkan.Core10.Enums.FrontFace

Zero FrontFace Source # 
Instance details

Defined in Vulkan.Core10.Enums.FrontFace

newtype BlendFactor Source #

VkBlendFactor - Framebuffer blending factors

Description

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

BlendFactor RGB Blend Factors (Sr,Sg,Sb) or (Dr,Dg,Db) Alpha Blend Factor (Sa or Da)
BLEND_FACTOR_ZERO (0,0,0) 0
BLEND_FACTOR_ONE (1,1,1) 1
BLEND_FACTOR_SRC_COLOR (Rs0,Gs0,Bs0) As0
BLEND_FACTOR_ONE_MINUS_SRC_COLOR (1-Rs0,1-Gs0,1-Bs0) 1-As0
BLEND_FACTOR_DST_COLOR (Rd,Gd,Bd) Ad
BLEND_FACTOR_ONE_MINUS_DST_COLOR (1-Rd,1-Gd,1-Bd) 1-Ad
BLEND_FACTOR_SRC_ALPHA (As0,As0,As0) As0
BLEND_FACTOR_ONE_MINUS_SRC_ALPHA (1-As0,1-As0,1-As0) 1-As0
BLEND_FACTOR_DST_ALPHA (Ad,Ad,Ad) Ad
BLEND_FACTOR_ONE_MINUS_DST_ALPHA (1-Ad,1-Ad,1-Ad) 1-Ad
BLEND_FACTOR_CONSTANT_COLOR (Rc,Gc,Bc) Ac
BLEND_FACTOR_ONE_MINUS_CONSTANT_COLOR (1-Rc,1-Gc,1-Bc) 1-Ac
BLEND_FACTOR_CONSTANT_ALPHA (Ac,Ac,Ac) Ac
BLEND_FACTOR_ONE_MINUS_CONSTANT_ALPHA (1-Ac,1-Ac,1-Ac) 1-Ac
BLEND_FACTOR_SRC_ALPHA_SATURATE (f,f,f); f = min(As0,1-Ad) 1
BLEND_FACTOR_SRC1_COLOR (Rs1,Gs1,Bs1) As1
BLEND_FACTOR_ONE_MINUS_SRC1_COLOR (1-Rs1,1-Gs1,1-Bs1) 1-As1
BLEND_FACTOR_SRC1_ALPHA (As1,As1,As1) As1
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

PipelineColorBlendAttachmentState

Constructors

BlendFactor Int32 

Instances

Instances details
Eq BlendFactor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BlendFactor

Ord BlendFactor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BlendFactor

Read BlendFactor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BlendFactor

Show BlendFactor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BlendFactor

Storable BlendFactor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BlendFactor

Zero BlendFactor Source # 
Instance details

Defined in Vulkan.Core10.Enums.BlendFactor

newtype BlendOp Source #

VkBlendOp - Framebuffer blending operations

Description

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

BlendOp RGB Components Alpha Component
BLEND_OP_ADD R = Rs0 × Sr + Rd × Dr G = Gs0 × Sg + Gd × Dg B = Bs0 × Sb + Bd × Db A = As0 × Sa + Ad × Da
BLEND_OP_SUBTRACT R = Rs0 × Sr - Rd × Dr G = Gs0 × Sg - Gd × Dg B = Bs0 × Sb - Bd × Db A = As0 × Sa - Ad × Da
BLEND_OP_REVERSE_SUBTRACT R = Rd × Dr - Rs0 × Sr G = Gd × Dg - Gs0 × Sg B = Bd × Db - Bs0 × Sb A = Ad × Da - As0 × Sa
BLEND_OP_MIN R = min(Rs0,Rd) G = min(Gs0,Gd) B = min(Bs0,Bd) A = min(As0,Ad)
BLEND_OP_MAX R = max(Rs0,Rd) G = max(Gs0,Gd) B = max(Bs0,Bd) A = max(As0,Ad)

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

PipelineColorBlendAttachmentState

Constructors

BlendOp Int32 

Bundled Patterns

pattern BLEND_OP_ADD :: BlendOp 
pattern BLEND_OP_SUBTRACT :: BlendOp 
pattern BLEND_OP_REVERSE_SUBTRACT :: BlendOp 
pattern BLEND_OP_MIN :: BlendOp 
pattern BLEND_OP_MAX :: BlendOp 
pattern BLEND_OP_BLUE_EXT :: BlendOp 
pattern BLEND_OP_GREEN_EXT :: BlendOp 
pattern BLEND_OP_RED_EXT :: BlendOp 
pattern BLEND_OP_INVERT_OVG_EXT :: BlendOp 
pattern BLEND_OP_CONTRAST_EXT :: BlendOp 
pattern BLEND_OP_MINUS_CLAMPED_EXT :: BlendOp 
pattern BLEND_OP_MINUS_EXT :: BlendOp 
pattern BLEND_OP_PLUS_DARKER_EXT :: BlendOp 
pattern BLEND_OP_PLUS_CLAMPED_ALPHA_EXT :: BlendOp 
pattern BLEND_OP_PLUS_CLAMPED_EXT :: BlendOp 
pattern BLEND_OP_PLUS_EXT :: BlendOp 
pattern BLEND_OP_HSL_LUMINOSITY_EXT :: BlendOp 
pattern BLEND_OP_HSL_COLOR_EXT :: BlendOp 
pattern BLEND_OP_HSL_SATURATION_EXT :: BlendOp 
pattern BLEND_OP_HSL_HUE_EXT :: BlendOp 
pattern BLEND_OP_HARDMIX_EXT :: BlendOp 
pattern BLEND_OP_PINLIGHT_EXT :: BlendOp 
pattern BLEND_OP_LINEARLIGHT_EXT :: BlendOp 
pattern BLEND_OP_VIVIDLIGHT_EXT :: BlendOp 
pattern BLEND_OP_LINEARBURN_EXT :: BlendOp 
pattern BLEND_OP_LINEARDODGE_EXT :: BlendOp 
pattern BLEND_OP_INVERT_RGB_EXT :: BlendOp 
pattern BLEND_OP_INVERT_EXT :: BlendOp 
pattern BLEND_OP_EXCLUSION_EXT :: BlendOp 
pattern BLEND_OP_DIFFERENCE_EXT :: BlendOp 
pattern BLEND_OP_SOFTLIGHT_EXT :: BlendOp 
pattern BLEND_OP_HARDLIGHT_EXT :: BlendOp 
pattern BLEND_OP_COLORBURN_EXT :: BlendOp 
pattern BLEND_OP_COLORDODGE_EXT :: BlendOp 
pattern BLEND_OP_LIGHTEN_EXT :: BlendOp 
pattern BLEND_OP_DARKEN_EXT :: BlendOp 
pattern BLEND_OP_OVERLAY_EXT :: BlendOp 
pattern BLEND_OP_SCREEN_EXT :: BlendOp 
pattern BLEND_OP_MULTIPLY_EXT :: BlendOp 
pattern BLEND_OP_XOR_EXT :: BlendOp 
pattern BLEND_OP_DST_ATOP_EXT :: BlendOp 
pattern BLEND_OP_SRC_ATOP_EXT :: BlendOp 
pattern BLEND_OP_DST_OUT_EXT :: BlendOp 
pattern BLEND_OP_SRC_OUT_EXT :: BlendOp 
pattern BLEND_OP_DST_IN_EXT :: BlendOp 
pattern BLEND_OP_SRC_IN_EXT :: BlendOp 
pattern BLEND_OP_DST_OVER_EXT :: BlendOp 
pattern BLEND_OP_SRC_OVER_EXT :: BlendOp 
pattern BLEND_OP_DST_EXT :: BlendOp 
pattern BLEND_OP_SRC_EXT :: BlendOp 
pattern BLEND_OP_ZERO_EXT :: BlendOp 

newtype StencilOp Source #

VkStencilOp - Stencil comparison function

Description

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

See Also

StencilOpState, cmdSetStencilOpEXT

Constructors

StencilOp Int32 

Bundled Patterns

pattern STENCIL_OP_KEEP :: StencilOp

STENCIL_OP_KEEP keeps the current value.

pattern STENCIL_OP_ZERO :: StencilOp

STENCIL_OP_ZERO sets the value to 0.

pattern STENCIL_OP_REPLACE :: StencilOp

STENCIL_OP_REPLACE sets the value to reference.

pattern STENCIL_OP_INCREMENT_AND_CLAMP :: StencilOp

STENCIL_OP_INCREMENT_AND_CLAMP increments the current value and clamps to the maximum representable unsigned value.

pattern STENCIL_OP_DECREMENT_AND_CLAMP :: StencilOp

STENCIL_OP_DECREMENT_AND_CLAMP decrements the current value and clamps to 0.

pattern STENCIL_OP_INVERT :: StencilOp

STENCIL_OP_INVERT bitwise-inverts the current value.

pattern STENCIL_OP_INCREMENT_AND_WRAP :: StencilOp

STENCIL_OP_INCREMENT_AND_WRAP increments the current value and wraps to 0 when the maximum value would have been exceeded.

pattern STENCIL_OP_DECREMENT_AND_WRAP :: StencilOp

STENCIL_OP_DECREMENT_AND_WRAP decrements the current value and wraps to the maximum possible value when the value would go below 0.

Instances

Instances details
Eq StencilOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.StencilOp

Ord StencilOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.StencilOp

Read StencilOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.StencilOp

Show StencilOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.StencilOp

Storable StencilOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.StencilOp

Zero StencilOp Source # 
Instance details

Defined in Vulkan.Core10.Enums.StencilOp

newtype LogicOp 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
LOGIC_OP_CLEAR 0
LOGIC_OP_AND s ∧ d
LOGIC_OP_AND_REVERSE s ∧ ¬ d
LOGIC_OP_COPY s
LOGIC_OP_AND_INVERTED ¬ s ∧ d
LOGIC_OP_NO_OP d
LOGIC_OP_XOR s ⊕ d
LOGIC_OP_OR s ∨ d
LOGIC_OP_NOR ¬ (s ∨ d)
LOGIC_OP_EQUIVALENT ¬ (s ⊕ d)
LOGIC_OP_INVERT ¬ d
LOGIC_OP_OR_REVERSE s ∨ ¬ d
LOGIC_OP_COPY_INVERTED ¬ s
LOGIC_OP_OR_INVERTED ¬ s ∨ d
LOGIC_OP_NAND ¬ (s ∧ d)
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

PipelineColorBlendStateCreateInfo

Constructors

LogicOp Int32 

newtype VertexInputRate Source #

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

See Also

VertexInputBindingDescription

Constructors

VertexInputRate Int32 

Bundled Patterns

pattern VERTEX_INPUT_RATE_VERTEX :: VertexInputRate

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

pattern VERTEX_INPUT_RATE_INSTANCE :: VertexInputRate

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

Instances

Instances details
Eq VertexInputRate Source # 
Instance details

Defined in Vulkan.Core10.Enums.VertexInputRate

Ord VertexInputRate Source # 
Instance details

Defined in Vulkan.Core10.Enums.VertexInputRate

Read VertexInputRate Source # 
Instance details

Defined in Vulkan.Core10.Enums.VertexInputRate

Show VertexInputRate Source # 
Instance details

Defined in Vulkan.Core10.Enums.VertexInputRate

Storable VertexInputRate Source # 
Instance details

Defined in Vulkan.Core10.Enums.VertexInputRate

Zero VertexInputRate Source # 
Instance details

Defined in Vulkan.Core10.Enums.VertexInputRate

newtype DynamicState Source #

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

See Also

PipelineDynamicStateCreateInfo

Constructors

DynamicState Int32 

Bundled Patterns

pattern DYNAMIC_STATE_VIEWPORT :: DynamicState

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

pattern DYNAMIC_STATE_SCISSOR :: DynamicState

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

pattern DYNAMIC_STATE_LINE_WIDTH :: DynamicState

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

pattern DYNAMIC_STATE_DEPTH_BIAS :: DynamicState

DYNAMIC_STATE_DEPTH_BIAS specifies that the depthBiasConstantFactor, depthBiasClamp and depthBiasSlopeFactor states in PipelineRasterizationStateCreateInfo will be ignored and must be set dynamically with cmdSetDepthBias before any draws are performed with depthBiasEnable in PipelineRasterizationStateCreateInfo set to TRUE.

pattern DYNAMIC_STATE_BLEND_CONSTANTS :: DynamicState

DYNAMIC_STATE_BLEND_CONSTANTS specifies that the blendConstants state in PipelineColorBlendStateCreateInfo will be ignored and must be set dynamically with cmdSetBlendConstants before any draws are performed with a pipeline state with PipelineColorBlendAttachmentState member blendEnable set to TRUE and any of the blend functions using a constant blend color.

pattern DYNAMIC_STATE_DEPTH_BOUNDS :: DynamicState

DYNAMIC_STATE_DEPTH_BOUNDS specifies that the minDepthBounds and maxDepthBounds states of PipelineDepthStencilStateCreateInfo will be ignored and must be set dynamically with cmdSetDepthBounds before any draws are performed with a pipeline state with PipelineDepthStencilStateCreateInfo member depthBoundsTestEnable set to TRUE.

pattern DYNAMIC_STATE_STENCIL_COMPARE_MASK :: DynamicState

DYNAMIC_STATE_STENCIL_COMPARE_MASK specifies that the compareMask state in PipelineDepthStencilStateCreateInfo for both front and back will be ignored and must be set dynamically with cmdSetStencilCompareMask before any draws are performed with a pipeline state with PipelineDepthStencilStateCreateInfo member stencilTestEnable set to TRUE

pattern DYNAMIC_STATE_STENCIL_WRITE_MASK :: DynamicState

DYNAMIC_STATE_STENCIL_WRITE_MASK specifies that the writeMask state in PipelineDepthStencilStateCreateInfo for both front and back will be ignored and must be set dynamically with cmdSetStencilWriteMask before any draws are performed with a pipeline state with PipelineDepthStencilStateCreateInfo member stencilTestEnable set to TRUE

pattern DYNAMIC_STATE_STENCIL_REFERENCE :: DynamicState

DYNAMIC_STATE_STENCIL_REFERENCE specifies that the reference state in PipelineDepthStencilStateCreateInfo for both front and back will be ignored and must be set dynamically with cmdSetStencilReference before any draws are performed with a pipeline state with PipelineDepthStencilStateCreateInfo member stencilTestEnable set to TRUE

pattern DYNAMIC_STATE_STENCIL_OP_EXT :: DynamicState

DYNAMIC_STATE_STENCIL_OP_EXT specifies that the failOp, passOp, depthFailOp, and compareOp states in PipelineDepthStencilStateCreateInfo for both front and back will be ignored and must be set dynamically with cmdSetStencilOpEXT before any draws are performed with a pipeline state with PipelineDepthStencilStateCreateInfo member stencilTestEnable set to TRUE

pattern DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT :: DynamicState

DYNAMIC_STATE_STENCIL_TEST_ENABLE_EXT specifies that the stencilTestEnable state in PipelineDepthStencilStateCreateInfo will be ignored and must be set dynamically with cmdSetStencilTestEnableEXT before any draw call.

pattern DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT :: DynamicState

DYNAMIC_STATE_DEPTH_BOUNDS_TEST_ENABLE_EXT specifies that the depthBoundsTestEnable state in PipelineDepthStencilStateCreateInfo will be ignored and must be set dynamically with cmdSetDepthBoundsTestEnableEXT before any draw call.

pattern DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT :: DynamicState

DYNAMIC_STATE_DEPTH_COMPARE_OP_EXT specifies that the depthCompareOp state in PipelineDepthStencilStateCreateInfo will be ignored and must be set dynamically with cmdSetDepthCompareOpEXT before any draw call.

pattern DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT :: DynamicState

DYNAMIC_STATE_DEPTH_WRITE_ENABLE_EXT specifies that the depthWriteEnable state in PipelineDepthStencilStateCreateInfo will be ignored and must be set dynamically with cmdSetDepthWriteEnableEXT before any draw call.

pattern DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT :: DynamicState

DYNAMIC_STATE_DEPTH_TEST_ENABLE_EXT specifies that the depthTestEnable state in PipelineDepthStencilStateCreateInfo will be ignored and must be set dynamically with cmdSetDepthTestEnableEXT before any draw call.

pattern DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT :: DynamicState

DYNAMIC_STATE_VERTEX_INPUT_BINDING_STRIDE_EXT specifies that the stride state in VertexInputBindingDescription will be ignored and must be set dynamically with cmdBindVertexBuffers2EXT before any draw call.

pattern DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT :: DynamicState

DYNAMIC_STATE_SCISSOR_WITH_COUNT_EXT specifies that the scissorCount and pScissors state in PipelineViewportStateCreateInfo will be ignored and must be set dynamically with cmdSetScissorWithCountEXT before any draw call.

pattern DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT :: DynamicState

DYNAMIC_STATE_VIEWPORT_WITH_COUNT_EXT specifies that the viewportCount and pViewports state in PipelineViewportStateCreateInfo will be ignored and must be set dynamically with cmdSetViewportWithCountEXT before any draw call.

pattern DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT :: DynamicState

DYNAMIC_STATE_PRIMITIVE_TOPOLOGY_EXT specifies that the topology state in PipelineInputAssemblyStateCreateInfo only specifies the topology class, and the specific topology order and adjacency must be set dynamically with cmdSetPrimitiveTopologyEXT before any draw commands.

pattern DYNAMIC_STATE_FRONT_FACE_EXT :: DynamicState

DYNAMIC_STATE_FRONT_FACE_EXT specifies that the frontFace state in PipelineRasterizationStateCreateInfo will be ignored and must be set dynamically with cmdSetFrontFaceEXT before any draw commands.

pattern DYNAMIC_STATE_CULL_MODE_EXT :: DynamicState

DYNAMIC_STATE_CULL_MODE_EXT specifies that the cullMode state in PipelineRasterizationStateCreateInfo will be ignored and must be set dynamically with cmdSetCullModeEXT before any draw commands.

pattern DYNAMIC_STATE_LINE_STIPPLE_EXT :: DynamicState

DYNAMIC_STATE_LINE_STIPPLE_EXT specifies that the lineStippleFactor and lineStipplePattern state in PipelineRasterizationLineStateCreateInfoEXT will be ignored and must be set dynamically with cmdSetLineStippleEXT before any draws are performed with a pipeline state with PipelineRasterizationLineStateCreateInfoEXT member stippledLineEnable set to TRUE.

pattern DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV :: DynamicState

DYNAMIC_STATE_EXCLUSIVE_SCISSOR_NV specifies that the pExclusiveScissors state in PipelineViewportExclusiveScissorStateCreateInfoNV will be ignored and must be set dynamically with cmdSetExclusiveScissorNV before any draw commands. The number of exclusive scissor rectangles used by a pipeline is still specified by the exclusiveScissorCount member of PipelineViewportExclusiveScissorStateCreateInfoNV.

pattern DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV :: DynamicState

DYNAMIC_STATE_VIEWPORT_COARSE_SAMPLE_ORDER_NV specifies that the coarse sample order state in PipelineViewportCoarseSampleOrderStateCreateInfoNV will be ignored and must be set dynamically with cmdSetCoarseSampleOrderNV before any draw commands.

pattern DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV :: DynamicState

DYNAMIC_STATE_VIEWPORT_SHADING_RATE_PALETTE_NV specifies that the pShadingRatePalettes state in PipelineViewportShadingRateImageStateCreateInfoNV will be ignored and must be set dynamically with cmdSetViewportShadingRatePaletteNV before any draw commands.

pattern DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT :: DynamicState

DYNAMIC_STATE_SAMPLE_LOCATIONS_EXT specifies that the sampleLocationsInfo state in PipelineSampleLocationsStateCreateInfoEXT will be ignored and must be set dynamically with cmdSetSampleLocationsEXT before any draw or clear commands. Enabling custom sample locations is still indicated by the sampleLocationsEnable member of PipelineSampleLocationsStateCreateInfoEXT.

pattern DYNAMIC_STATE_DISCARD_RECTANGLE_EXT :: DynamicState

DYNAMIC_STATE_DISCARD_RECTANGLE_EXT specifies that the pDiscardRectangles state in PipelineDiscardRectangleStateCreateInfoEXT will be ignored and must be set dynamically with cmdSetDiscardRectangleEXT before any draw or clear commands. The DiscardRectangleModeEXT and the number of active discard rectangles is still specified by the discardRectangleMode and discardRectangleCount members of PipelineDiscardRectangleStateCreateInfoEXT.

pattern DYNAMIC_STATE_VIEWPORT_W_SCALING_NV :: DynamicState

DYNAMIC_STATE_VIEWPORT_W_SCALING_NV specifies that the pViewportScalings state in PipelineViewportWScalingStateCreateInfoNV will be ignored and must be set dynamically with cmdSetViewportWScalingNV before any draws are performed with a pipeline state with PipelineViewportWScalingStateCreateInfoNV member viewportScalingEnable set to TRUE

Instances

Instances details
Eq DynamicState Source # 
Instance details

Defined in Vulkan.Core10.Enums.DynamicState

Ord DynamicState Source # 
Instance details

Defined in Vulkan.Core10.Enums.DynamicState

Read DynamicState Source # 
Instance details

Defined in Vulkan.Core10.Enums.DynamicState

Show DynamicState Source # 
Instance details

Defined in Vulkan.Core10.Enums.DynamicState

Storable DynamicState Source # 
Instance details

Defined in Vulkan.Core10.Enums.DynamicState

Zero DynamicState Source # 
Instance details

Defined in Vulkan.Core10.Enums.DynamicState

newtype ShaderStageFlagBits Source #

VkShaderStageFlagBits - Bitmask specifying a pipeline stage

Description

Note

SHADER_STAGE_ALL_GRAPHICS only includes the original five graphics stages included in Vulkan 1.0, and not any stages added by extensions. Thus, it may not have the desired effect in all cases.

See Also

PipelineShaderStageCreateInfo, ShaderStageFlags, getShaderInfoAMD

Bundled Patterns

pattern SHADER_STAGE_VERTEX_BIT :: ShaderStageFlagBits

SHADER_STAGE_VERTEX_BIT specifies the vertex stage.

pattern SHADER_STAGE_TESSELLATION_CONTROL_BIT :: ShaderStageFlagBits

SHADER_STAGE_TESSELLATION_CONTROL_BIT specifies the tessellation control stage.

pattern SHADER_STAGE_TESSELLATION_EVALUATION_BIT :: ShaderStageFlagBits

SHADER_STAGE_TESSELLATION_EVALUATION_BIT specifies the tessellation evaluation stage.

pattern SHADER_STAGE_GEOMETRY_BIT :: ShaderStageFlagBits

SHADER_STAGE_GEOMETRY_BIT specifies the geometry stage.

pattern SHADER_STAGE_FRAGMENT_BIT :: ShaderStageFlagBits

SHADER_STAGE_FRAGMENT_BIT specifies the fragment stage.

pattern SHADER_STAGE_COMPUTE_BIT :: ShaderStageFlagBits

SHADER_STAGE_COMPUTE_BIT specifies the compute stage.

pattern SHADER_STAGE_ALL_GRAPHICS :: ShaderStageFlagBits

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

pattern SHADER_STAGE_ALL :: ShaderStageFlagBits

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.

pattern SHADER_STAGE_MESH_BIT_NV :: ShaderStageFlagBits

SHADER_STAGE_MESH_BIT_NV specifies the mesh stage.

pattern SHADER_STAGE_TASK_BIT_NV :: ShaderStageFlagBits

SHADER_STAGE_TASK_BIT_NV specifies the task stage.

pattern SHADER_STAGE_CALLABLE_BIT_KHR :: ShaderStageFlagBits

SHADER_STAGE_CALLABLE_BIT_KHR specifies the callable stage.

pattern SHADER_STAGE_INTERSECTION_BIT_KHR :: ShaderStageFlagBits

SHADER_STAGE_INTERSECTION_BIT_KHR specifies the intersection stage.

pattern SHADER_STAGE_MISS_BIT_KHR :: ShaderStageFlagBits

SHADER_STAGE_MISS_BIT_KHR specifies the miss stage.

pattern SHADER_STAGE_CLOSEST_HIT_BIT_KHR :: ShaderStageFlagBits

SHADER_STAGE_CLOSEST_HIT_BIT_KHR specifies the closest hit stage.

pattern SHADER_STAGE_ANY_HIT_BIT_KHR :: ShaderStageFlagBits

SHADER_STAGE_ANY_HIT_BIT_KHR specifies the any-hit stage.

pattern SHADER_STAGE_RAYGEN_BIT_KHR :: ShaderStageFlagBits

SHADER_STAGE_RAYGEN_BIT_KHR specifies the ray generation stage.

Instances

Instances details
Eq ShaderStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderStageFlagBits

Ord ShaderStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderStageFlagBits

Read ShaderStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderStageFlagBits

Show ShaderStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderStageFlagBits

Storable ShaderStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderStageFlagBits

Bits ShaderStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderStageFlagBits

Zero ShaderStageFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ShaderStageFlagBits

newtype PipelineCreateFlagBits Source #

VkPipelineCreateFlagBits - Bitmask controlling how a pipeline is created

Description

It is valid to set both PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT and 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

PipelineCreateFlags

Instances

Instances details
Eq PipelineCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineCreateFlagBits

Ord PipelineCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineCreateFlagBits

Read PipelineCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineCreateFlagBits

Show PipelineCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineCreateFlagBits

Storable PipelineCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineCreateFlagBits

Bits PipelineCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineCreateFlagBits

Zero PipelineCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineCreateFlagBits

newtype PipelineShaderStageCreateFlagBits Source #

VkPipelineShaderStageCreateFlagBits - Bitmask controlling how a pipeline shader stage is created

Description

Note

If PIPELINE_SHADER_STAGE_CREATE_ALLOW_VARYING_SUBGROUP_SIZE_BIT_EXT and PIPELINE_SHADER_STAGE_CREATE_REQUIRE_FULL_SUBGROUPS_BIT_EXT are specified and minSubgroupSize does not equal maxSubgroupSize and no required subgroup size is specified, then the only way to guarantee that the 'X' dimension of the local workgroup size is a multiple of SubgroupSize is to make it a multiple of maxSubgroupSize. Under these conditions, you are guaranteed full subgroups but not any particular subgroup size.

See Also

PipelineShaderStageCreateFlags

Instances

Instances details
Eq PipelineShaderStageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits

Ord PipelineShaderStageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits

Read PipelineShaderStageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits

Show PipelineShaderStageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits

Storable PipelineShaderStageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits

Bits PipelineShaderStageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits

Methods

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

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

xor :: PipelineShaderStageCreateFlagBits -> PipelineShaderStageCreateFlagBits -> PipelineShaderStageCreateFlagBits #

complement :: PipelineShaderStageCreateFlagBits -> PipelineShaderStageCreateFlagBits #

shift :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

rotate :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

zeroBits :: PipelineShaderStageCreateFlagBits #

bit :: Int -> PipelineShaderStageCreateFlagBits #

setBit :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

clearBit :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

complementBit :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

testBit :: PipelineShaderStageCreateFlagBits -> Int -> Bool #

bitSizeMaybe :: PipelineShaderStageCreateFlagBits -> Maybe Int #

bitSize :: PipelineShaderStageCreateFlagBits -> Int #

isSigned :: PipelineShaderStageCreateFlagBits -> Bool #

shiftL :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

unsafeShiftL :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

shiftR :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

unsafeShiftR :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

rotateL :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

rotateR :: PipelineShaderStageCreateFlagBits -> Int -> PipelineShaderStageCreateFlagBits #

popCount :: PipelineShaderStageCreateFlagBits -> Int #

Zero PipelineShaderStageCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.PipelineShaderStageCreateFlagBits

newtype ColorComponentFlagBits Source #

VkColorComponentFlagBits - Bitmask controlling which components are written to the framebuffer

Description

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

See Also

ColorComponentFlags

Bundled Patterns

pattern COLOR_COMPONENT_R_BIT :: ColorComponentFlagBits

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.

pattern COLOR_COMPONENT_G_BIT :: ColorComponentFlagBits

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.

pattern COLOR_COMPONENT_B_BIT :: ColorComponentFlagBits

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.

pattern COLOR_COMPONENT_A_BIT :: ColorComponentFlagBits

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.

Instances

Instances details
Eq ColorComponentFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ColorComponentFlagBits

Ord ColorComponentFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ColorComponentFlagBits

Read ColorComponentFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ColorComponentFlagBits

Show ColorComponentFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ColorComponentFlagBits

Storable ColorComponentFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ColorComponentFlagBits

Bits ColorComponentFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ColorComponentFlagBits

Zero ColorComponentFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.ColorComponentFlagBits

type SampleMask = Word32 Source #

VkSampleMask - Mask of sample coverage information

See Also

PipelineMultisampleStateCreateInfo