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

Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Synopsis

Documentation

createRenderPass2 Source #

Arguments

:: forall a io. (Extendss RenderPassCreateInfo2 a, PokeChain a, MonadIO io) 
=> Device

device is the logical device that creates the render pass.

-> RenderPassCreateInfo2 a

pCreateInfo is a pointer to a RenderPassCreateInfo2 structure describing the parameters of the render pass.

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

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

-> io RenderPass 

vkCreateRenderPass2 - Create a new render pass object

Description

This command is functionally identical to createRenderPass, but includes extensible sub-structures that include sType and pNext parameters, allowing them to be more easily extended.

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, RenderPass, RenderPassCreateInfo2

cmdBeginRenderPass2 Source #

Arguments

:: forall a io. (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) 
=> CommandBuffer

commandBuffer is the command buffer in which to record the command.

-> RenderPassBeginInfo a

pRenderPassBegin is a pointer to a RenderPassBeginInfo structure specifying the render pass to begin an instance of, and the framebuffer the instance uses.

-> SubpassBeginInfo

pSubpassBeginInfo is a pointer to a SubpassBeginInfo structure containing information about the subpass which is about to begin rendering.

-> io () 

vkCmdBeginRenderPass2 - Begin a new render pass

Description

After beginning a render pass instance, the command buffer is ready to record the commands for the first subpass of that render pass.

Valid Usage

  • Both the framebuffer and renderPass members of pRenderPassBegin must have been created on the same Device that commandBuffer was allocated on

Valid Usage (Implicit)

  • pRenderPassBegin must be a valid pointer to a valid RenderPassBeginInfo structure
  • pSubpassBeginInfo must be a valid pointer to a valid SubpassBeginInfo structure
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics operations
  • This command must only be called outside of a render pass instance
  • commandBuffer must be a primary CommandBuffer

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Outside Graphics Graphics

See Also

CommandBuffer, RenderPassBeginInfo, SubpassBeginInfo

cmdUseRenderPass2 :: forall a io r. (Extendss RenderPassBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> RenderPassBeginInfo a -> SubpassBeginInfo -> SubpassEndInfo -> io r -> io r Source #

This function will call the supplied action between calls to cmdBeginRenderPass2 and cmdEndRenderPass2

Note that cmdEndRenderPass2 is *not* called if an exception is thrown by the inner action.

cmdNextSubpass2 Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer in which to record the command.

-> SubpassBeginInfo

pSubpassBeginInfo is a pointer to a SubpassBeginInfo structure containing information about the subpass which is about to begin rendering.

-> SubpassEndInfo

pSubpassEndInfo is a pointer to a SubpassEndInfo structure containing information about how the previous subpass will be ended.

-> io () 

vkCmdNextSubpass2 - Transition to the next subpass of a render pass

Description

cmdNextSubpass2 is semantically identical to cmdNextSubpass, except that it is extensible, and that contents is provided as part of an extensible structure instead of as a flat parameter.

Valid Usage

  • The current subpass index must be less than the number of subpasses in the render pass minus one
  • This command must not be recorded when transform feedback is active

Valid Usage (Implicit)

  • pSubpassBeginInfo must be a valid pointer to a valid SubpassBeginInfo structure
  • pSubpassEndInfo must be a valid pointer to a valid SubpassEndInfo structure
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics operations
  • This command must only be called inside of a render pass instance
  • commandBuffer must be a primary CommandBuffer

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Inside Graphics Graphics

See Also

CommandBuffer, SubpassBeginInfo, SubpassEndInfo

cmdEndRenderPass2 Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer in which to end the current render pass instance.

-> SubpassEndInfo

pSubpassEndInfo is a pointer to a SubpassEndInfo structure containing information about how the previous subpass will be ended.

-> io () 

vkCmdEndRenderPass2 - End the current render pass

Description

cmdEndRenderPass2 is semantically identical to cmdEndRenderPass, except that it is extensible.

Valid Usage

  • The current subpass index must be equal to the number of subpasses in the render pass minus one
  • This command must not be recorded when transform feedback is active

Valid Usage (Implicit)

  • pSubpassEndInfo must be a valid pointer to a valid SubpassEndInfo structure
  • commandBuffer must be in the recording state
  • The CommandPool that commandBuffer was allocated from must support graphics operations
  • This command must only be called inside of a render pass instance
  • commandBuffer must be a primary CommandBuffer

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
Primary Inside Graphics Graphics

See Also

CommandBuffer, SubpassEndInfo

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

VkAttachmentDescription2 - Structure specifying an attachment description

Description

Parameters defined by this structure with the same name as those in AttachmentDescription have the identical effect to those parameters.

If the separateDepthStencilLayouts feature is enabled, and format is a depth/stencil format, initialLayout and finalLayout can be set to a layout that only specifies the layout of the depth aspect.

If format is a depth/stencil format, and initialLayout only specifies the initial layout of the depth aspect of the attachment, the initial layout of the stencil aspect is specified by the stencilInitialLayout member of a AttachmentDescriptionStencilLayout structure included in the pNext chain. Otherwise, initialLayout describes the initial layout for all relevant image aspects.

If format is a depth/stencil format, and finalLayout only specifies the final layout of the depth aspect of the attachment, the final layout of the stencil aspect is specified by the stencilFinalLayout member of a AttachmentDescriptionStencilLayout structure included in the pNext chain. Otherwise, finalLayout describes the final layout for all relevant image aspects.

Valid Usage

Valid Usage (Implicit)

See Also

AttachmentDescriptionFlags, AttachmentLoadOp, AttachmentStoreOp, Format, ImageLayout, RenderPassCreateInfo2, SampleCountFlagBits, StructureType

Constructors

AttachmentDescription2 

Fields

Instances

Instances details
Extensible AttachmentDescription2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Generic (AttachmentDescription2 es) Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Associated Types

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

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep (AttachmentDescription2 es) Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

VkAttachmentReference2 - Structure specifying an attachment reference

Description

Parameters defined by this structure with the same name as those in AttachmentReference have the identical effect to those parameters.

aspectMask is ignored when this structure is used to describe anything other than an input attachment reference.

If the separateDepthStencilLayouts feature is enabled, and attachment has a depth/stencil format, layout can be set to a layout that only specifies the layout of the depth aspect.

If layout only specifies the layout of the depth aspect of the attachment, the layout of the stencil aspect is specified by the stencilLayout member of a AttachmentReferenceStencilLayout structure included in the pNext chain. Otherwise, layout describes the layout for all relevant image aspects.

Valid Usage

Valid Usage (Implicit)

See Also

ImageAspectFlags, ImageLayout, StructureType, SubpassDescription2, SubpassDescriptionDepthStencilResolve

Constructors

AttachmentReference2 

Fields

Instances

Instances details
Extensible AttachmentReference2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Generic (AttachmentReference2 es) Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Associated Types

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

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep (AttachmentReference2 es) Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep (AttachmentReference2 es) = D1 ('MetaData "AttachmentReference2" "Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2" "vulkan-3.5-inplace" 'False) (C1 ('MetaCons "AttachmentReference2" 'PrefixI 'True) ((S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: S1 ('MetaSel ('Just "attachment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "layout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageLayout) :*: S1 ('MetaSel ('Just "aspectMask") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageAspectFlags))))

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

VkSubpassDescription2 - Structure specifying a subpass description

Description

Parameters defined by this structure with the same name as those in SubpassDescription have the identical effect to those parameters.

viewMask has the same effect for the described subpass as RenderPassMultiviewCreateInfo::pViewMasks has on each corresponding subpass.

Valid Usage

Valid Usage (Implicit)

  • flags must be a valid combination of SubpassDescriptionFlagBits values
  • pipelineBindPoint must be a valid PipelineBindPoint value
  • If inputAttachmentCount is not 0, pInputAttachments must be a valid pointer to an array of inputAttachmentCount valid AttachmentReference2 structures
  • If colorAttachmentCount is not 0, pColorAttachments must be a valid pointer to an array of colorAttachmentCount valid AttachmentReference2 structures
  • If colorAttachmentCount is not 0, and pResolveAttachments is not NULL, pResolveAttachments must be a valid pointer to an array of colorAttachmentCount valid AttachmentReference2 structures
  • If pDepthStencilAttachment is not NULL, pDepthStencilAttachment must be a valid pointer to a valid AttachmentReference2 structure
  • If preserveAttachmentCount is not 0, pPreserveAttachments must be a valid pointer to an array of preserveAttachmentCount uint32_t values

See Also

AttachmentReference2, PipelineBindPoint, RenderPassCreateInfo2, StructureType, SubpassDescriptionFlags

Constructors

SubpassDescription2 

Fields

Instances

Instances details
Extensible SubpassDescription2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Generic (SubpassDescription2 es) Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Associated Types

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

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep (SubpassDescription2 es) Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

data SubpassDependency2 Source #

VkSubpassDependency2 - Structure specifying a subpass dependency

Description

Parameters defined by this structure with the same name as those in SubpassDependency have the identical effect to those parameters.

viewOffset has the same effect for the described subpass dependency as RenderPassMultiviewCreateInfo::pViewOffsets has on each corresponding subpass dependency.

Valid Usage

Valid Usage (Implicit)

See Also

AccessFlags, DependencyFlags, PipelineStageFlags, RenderPassCreateInfo2, StructureType

Constructors

SubpassDependency2 

Fields

Instances

Instances details
Eq SubpassDependency2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Show SubpassDependency2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Generic SubpassDependency2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Associated Types

type Rep SubpassDependency2 :: Type -> Type #

Storable SubpassDependency2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

FromCStruct SubpassDependency2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

ToCStruct SubpassDependency2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Zero SubpassDependency2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep SubpassDependency2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

VkRenderPassCreateInfo2 - Structure specifying parameters of a newly created render pass

Description

Parameters defined by this structure with the same name as those in RenderPassCreateInfo have the identical effect to those parameters; the child structures are variants of those used in RenderPassCreateInfo which add sType and pNext parameters, allowing them to be extended.

If the SubpassDescription2::viewMask member of any element of pSubpasses is not zero, multiview functionality is considered to be enabled for this render pass.

correlatedViewMaskCount and pCorrelatedViewMasks have the same effect as RenderPassMultiviewCreateInfo::correlationMaskCount and RenderPassMultiviewCreateInfo::pCorrelationMasks, respectively.

Valid Usage

  • If any two subpasses operate on attachments with overlapping ranges of the same DeviceMemory object, and at least one subpass writes to that area of DeviceMemory, a subpass dependency must be included (either directly or via some intermediate subpasses) between them
  • If the attachment member of any element of pInputAttachments, pColorAttachments, pResolveAttachments or pDepthStencilAttachment, or the attachment indexed by any element of pPreserveAttachments in any given element of pSubpasses is bound to a range of a DeviceMemory object that overlaps with any other attachment in any subpass (including the same subpass), the AttachmentDescription2 structures describing them must include ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT in flags
  • If the attachment member of any element of pInputAttachments, pColorAttachments, pResolveAttachments or pDepthStencilAttachment, or any element of pPreserveAttachments in any given element of pSubpasses is not ATTACHMENT_UNUSED, it must be less than attachmentCount
  • For any member of pAttachments with a loadOp equal to ATTACHMENT_LOAD_OP_CLEAR, the first use of that attachment must not specify a layout equal to IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL, IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL, or IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL
  • For any member of pAttachments with a stencilLoadOp equal to ATTACHMENT_LOAD_OP_CLEAR, the first use of that attachment must not specify a layout equal to IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL, IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL, or IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL
  • For any element of pDependencies, if the srcSubpass is not SUBPASS_EXTERNAL, all stage flags included in the srcStageMask member of that dependency must be a pipeline stage supported by the pipeline identified by the pipelineBindPoint member of the source subpass
  • For any element of pDependencies, if the dstSubpass is not SUBPASS_EXTERNAL, all stage flags included in the dstStageMask member of that dependency must be a pipeline stage supported by the pipeline identified by the pipelineBindPoint member of the destination subpass
  • The set of bits included in any element of pCorrelatedViewMasks must not overlap with the set of bits included in any other element of pCorrelatedViewMasks
  • If the SubpassDescription2::viewMask member of all elements of pSubpasses is 0, correlatedViewMaskCount must be 0
  • The SubpassDescription2::viewMask member of all elements of pSubpasses must either all be 0, or all not be 0
  • If the SubpassDescription2::viewMask member of all elements of pSubpasses is 0, the dependencyFlags member of any element of pDependencies must not include DEPENDENCY_VIEW_LOCAL_BIT
  • For any element of pDependencies where its srcSubpass member equals its dstSubpass member, if the viewMask member of the corresponding element of pSubpasses includes more than one bit, its dependencyFlags member must include DEPENDENCY_VIEW_LOCAL_BIT
  • The viewMask member must not have a bit set at an index greater than or equal to PhysicalDeviceLimits::maxFramebufferLayers
  • If the attachment member of any element of the pInputAttachments member of any element of pSubpasses is not ATTACHMENT_UNUSED, the aspectMask member of that element of pInputAttachments must only include aspects that are present in images of the format specified by the element of pAttachments specified by attachment
  • The srcSubpass member of each element of pDependencies must be less than subpassCount
  • The dstSubpass member of each element of pDependencies must be less than subpassCount

Valid Usage (Implicit)

  • pNext must be NULL or a pointer to a valid instance of RenderPassFragmentDensityMapCreateInfoEXT
  • The sType value of each struct in the pNext chain must be unique
  • flags must be a valid combination of RenderPassCreateFlagBits values
  • If attachmentCount is not 0, pAttachments must be a valid pointer to an array of attachmentCount valid AttachmentDescription2 structures
  • pSubpasses must be a valid pointer to an array of subpassCount valid SubpassDescription2 structures
  • If dependencyCount is not 0, pDependencies must be a valid pointer to an array of dependencyCount valid SubpassDependency2 structures
  • If correlatedViewMaskCount is not 0, pCorrelatedViewMasks must be a valid pointer to an array of correlatedViewMaskCount uint32_t values
  • subpassCount must be greater than 0

See Also

AttachmentDescription2, RenderPassCreateFlags, StructureType, SubpassDependency2, SubpassDescription2, createRenderPass2, createRenderPass2KHR

Constructors

RenderPassCreateInfo2 

Fields

Instances

Instances details
Extensible RenderPassCreateInfo2 Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Generic (RenderPassCreateInfo2 es) Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Associated Types

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

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

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

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep (RenderPassCreateInfo2 es) Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

data SubpassBeginInfo Source #

VkSubpassBeginInfo - Structure specifying subpass begin info

Valid Usage (Implicit)

See Also

StructureType, SubpassContents, cmdBeginRenderPass2, cmdBeginRenderPass2KHR, cmdNextSubpass2, cmdNextSubpass2KHR

Constructors

SubpassBeginInfo 

Fields

Instances

Instances details
Eq SubpassBeginInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Show SubpassBeginInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Generic SubpassBeginInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Associated Types

type Rep SubpassBeginInfo :: Type -> Type #

Storable SubpassBeginInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

FromCStruct SubpassBeginInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

ToCStruct SubpassBeginInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Zero SubpassBeginInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep SubpassBeginInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep SubpassBeginInfo = D1 ('MetaData "SubpassBeginInfo" "Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2" "vulkan-3.5-inplace" 'False) (C1 ('MetaCons "SubpassBeginInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "contents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SubpassContents)))

data SubpassEndInfo Source #

VkSubpassEndInfo - Structure specifying subpass end info

Valid Usage (Implicit)

See Also

StructureType, cmdEndRenderPass2, cmdEndRenderPass2KHR, cmdNextSubpass2, cmdNextSubpass2KHR

Constructors

SubpassEndInfo 

Instances

Instances details
Eq SubpassEndInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Show SubpassEndInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Generic SubpassEndInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Associated Types

type Rep SubpassEndInfo :: Type -> Type #

Storable SubpassEndInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

FromCStruct SubpassEndInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

ToCStruct SubpassEndInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

Zero SubpassEndInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep SubpassEndInfo Source # 
Instance details

Defined in Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2

type Rep SubpassEndInfo = D1 ('MetaData "SubpassEndInfo" "Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2" "vulkan-3.5-inplace" 'False) (C1 ('MetaCons "SubpassEndInfo" 'PrefixI 'False) (U1 :: Type -> Type))

newtype StructureType Source #

VkStructureType - Vulkan structure types (sType)

Description

Each value corresponds to a particular structure with a sType member with a matching name. As a general rule, the name of each StructureType value is obtained by taking the name of the structure, stripping the leading Vk, prefixing each capital letter with _, converting the entire resulting string to upper case, and prefixing it with VK_STRUCTURE_TYPE_. For example, structures of type ImageCreateInfo correspond to a StructureType of STRUCTURE_TYPE_IMAGE_CREATE_INFO, and thus its sType member must equal that when it is passed to the API.

The values STRUCTURE_TYPE_LOADER_INSTANCE_CREATE_INFO and STRUCTURE_TYPE_LOADER_DEVICE_CREATE_INFO are reserved for internal use by the loader, and do not have corresponding Vulkan structures in this Specification.

See Also

AccelerationStructureBuildGeometryInfoKHR, AccelerationStructureCreateGeometryTypeInfoKHR, AccelerationStructureCreateInfoKHR, AccelerationStructureCreateInfoNV, AccelerationStructureDeviceAddressInfoKHR, AccelerationStructureGeometryAabbsDataKHR, AccelerationStructureGeometryInstancesDataKHR, AccelerationStructureGeometryKHR, AccelerationStructureGeometryTrianglesDataKHR, AccelerationStructureInfoNV, AccelerationStructureMemoryRequirementsInfoKHR, AccelerationStructureMemoryRequirementsInfoNV, AccelerationStructureVersionKHR, AcquireNextImageInfoKHR, AcquireProfilingLockInfoKHR, AndroidHardwareBufferFormatPropertiesANDROID, AndroidHardwareBufferPropertiesANDROID, AndroidHardwareBufferUsageANDROID, AndroidSurfaceCreateInfoKHR, ApplicationInfo, AttachmentDescription2, AttachmentDescriptionStencilLayout, AttachmentReference2, AttachmentReferenceStencilLayout, BaseInStructure, BaseOutStructure, BindAccelerationStructureMemoryInfoKHR, BindBufferMemoryDeviceGroupInfo, BindBufferMemoryInfo, BindImageMemoryDeviceGroupInfo, BindImageMemoryInfo, BindImageMemorySwapchainInfoKHR, BindImagePlaneMemoryInfo, BindSparseInfo, BufferCreateInfo, BufferDeviceAddressCreateInfoEXT, BufferDeviceAddressInfo, BufferMemoryBarrier, BufferMemoryRequirementsInfo2, BufferOpaqueCaptureAddressCreateInfo, BufferViewCreateInfo, CalibratedTimestampInfoEXT, CheckpointDataNV, CommandBufferAllocateInfo, CommandBufferBeginInfo, CommandBufferInheritanceConditionalRenderingInfoEXT, CommandBufferInheritanceInfo, CommandBufferInheritanceRenderPassTransformInfoQCOM, CommandPoolCreateInfo, ComputePipelineCreateInfo, ConditionalRenderingBeginInfoEXT, CooperativeMatrixPropertiesNV, CopyAccelerationStructureInfoKHR, CopyAccelerationStructureToMemoryInfoKHR, CopyDescriptorSet, CopyMemoryToAccelerationStructureInfoKHR, D3D12FenceSubmitInfoKHR, DebugMarkerMarkerInfoEXT, DebugMarkerObjectNameInfoEXT, DebugMarkerObjectTagInfoEXT, DebugReportCallbackCreateInfoEXT, DebugUtilsLabelEXT, DebugUtilsMessengerCallbackDataEXT, DebugUtilsMessengerCreateInfoEXT, DebugUtilsObjectNameInfoEXT, DebugUtilsObjectTagInfoEXT, DedicatedAllocationBufferCreateInfoNV, DedicatedAllocationImageCreateInfoNV, DedicatedAllocationMemoryAllocateInfoNV, DeferredOperationInfoKHR, DescriptorPoolCreateInfo, DescriptorPoolInlineUniformBlockCreateInfoEXT, DescriptorSetAllocateInfo, DescriptorSetLayoutBindingFlagsCreateInfo, DescriptorSetLayoutCreateInfo, DescriptorSetLayoutSupport, DescriptorSetVariableDescriptorCountAllocateInfo, DescriptorSetVariableDescriptorCountLayoutSupport, DescriptorUpdateTemplateCreateInfo, DeviceCreateInfo, DeviceDiagnosticsConfigCreateInfoNV, DeviceEventInfoEXT, DeviceGroupBindSparseInfo, DeviceGroupCommandBufferBeginInfo, DeviceGroupDeviceCreateInfo, DeviceGroupPresentCapabilitiesKHR, DeviceGroupPresentInfoKHR, DeviceGroupRenderPassBeginInfo, DeviceGroupSubmitInfo, DeviceGroupSwapchainCreateInfoKHR, DeviceMemoryOpaqueCaptureAddressInfo, DeviceMemoryOverallocationCreateInfoAMD, DevicePrivateDataCreateInfoEXT, DeviceQueueCreateInfo, DeviceQueueGlobalPriorityCreateInfoEXT, DeviceQueueInfo2, DisplayEventInfoEXT, DisplayModeCreateInfoKHR, DisplayModeProperties2KHR, DisplayNativeHdrSurfaceCapabilitiesAMD, DisplayPlaneCapabilities2KHR, DisplayPlaneInfo2KHR, DisplayPlaneProperties2KHR, DisplayPowerInfoEXT, DisplayPresentInfoKHR, DisplayProperties2KHR, DisplaySurfaceCreateInfoKHR, DrmFormatModifierPropertiesListEXT, EventCreateInfo, ExportFenceCreateInfo, ExportFenceWin32HandleInfoKHR, ExportMemoryAllocateInfo, ExportMemoryAllocateInfoNV, ExportMemoryWin32HandleInfoKHR, ExportMemoryWin32HandleInfoNV, ExportSemaphoreCreateInfo, ExportSemaphoreWin32HandleInfoKHR, ExternalBufferProperties, ExternalFenceProperties, ExternalFormatANDROID, ExternalImageFormatProperties, ExternalMemoryBufferCreateInfo, ExternalMemoryImageCreateInfo, ExternalMemoryImageCreateInfoNV, ExternalSemaphoreProperties, FenceCreateInfo, FenceGetFdInfoKHR, FenceGetWin32HandleInfoKHR, FilterCubicImageViewImageFormatPropertiesEXT, FormatProperties2, FramebufferAttachmentImageInfo, FramebufferAttachmentsCreateInfo, FramebufferCreateInfo, FramebufferMixedSamplesCombinationNV, GeneratedCommandsInfoNV, GeneratedCommandsMemoryRequirementsInfoNV, GeometryAABBNV, GeometryNV, GeometryTrianglesNV, GraphicsPipelineCreateInfo, GraphicsPipelineShaderGroupsCreateInfoNV, GraphicsShaderGroupCreateInfoNV, HdrMetadataEXT, HeadlessSurfaceCreateInfoEXT, IOSSurfaceCreateInfoMVK, ImageCreateInfo, ImageDrmFormatModifierExplicitCreateInfoEXT, ImageDrmFormatModifierListCreateInfoEXT, ImageDrmFormatModifierPropertiesEXT, ImageFormatListCreateInfo, ImageFormatProperties2, ImageMemoryBarrier, ImageMemoryRequirementsInfo2, ImagePipeSurfaceCreateInfoFUCHSIA, ImagePlaneMemoryRequirementsInfo, ImageSparseMemoryRequirementsInfo2, ImageStencilUsageCreateInfo, ImageSwapchainCreateInfoKHR, ImageViewASTCDecodeModeEXT, ImageViewAddressPropertiesNVX, ImageViewCreateInfo, ImageViewHandleInfoNVX, ImageViewUsageCreateInfo, ImportAndroidHardwareBufferInfoANDROID, ImportFenceFdInfoKHR, ImportFenceWin32HandleInfoKHR, ImportMemoryFdInfoKHR, ImportMemoryHostPointerInfoEXT, ImportMemoryWin32HandleInfoKHR, ImportMemoryWin32HandleInfoNV, ImportSemaphoreFdInfoKHR, ImportSemaphoreWin32HandleInfoKHR, IndirectCommandsLayoutCreateInfoNV, IndirectCommandsLayoutTokenNV, InitializePerformanceApiInfoINTEL, InstanceCreateInfo, MacOSSurfaceCreateInfoMVK, MappedMemoryRange, MemoryAllocateFlagsInfo, MemoryAllocateInfo, MemoryBarrier, MemoryDedicatedAllocateInfo, MemoryDedicatedRequirements, MemoryFdPropertiesKHR, MemoryGetAndroidHardwareBufferInfoANDROID, MemoryGetFdInfoKHR, MemoryGetWin32HandleInfoKHR, MemoryHostPointerPropertiesEXT, MemoryOpaqueCaptureAddressAllocateInfo, MemoryPriorityAllocateInfoEXT, MemoryRequirements2, MemoryWin32HandlePropertiesKHR, MetalSurfaceCreateInfoEXT, MultisamplePropertiesEXT, PerformanceConfigurationAcquireInfoINTEL, PerformanceCounterDescriptionKHR, PerformanceCounterKHR, PerformanceMarkerInfoINTEL, PerformanceOverrideInfoINTEL, PerformanceQuerySubmitInfoKHR, PerformanceStreamMarkerInfoINTEL, PhysicalDevice16BitStorageFeatures, PhysicalDevice8BitStorageFeatures, PhysicalDeviceASTCDecodeFeaturesEXT, PhysicalDeviceBlendOperationAdvancedFeaturesEXT, PhysicalDeviceBlendOperationAdvancedPropertiesEXT, PhysicalDeviceBufferDeviceAddressFeatures, PhysicalDeviceBufferDeviceAddressFeaturesEXT, PhysicalDeviceCoherentMemoryFeaturesAMD, PhysicalDeviceComputeShaderDerivativesFeaturesNV, PhysicalDeviceConditionalRenderingFeaturesEXT, PhysicalDeviceConservativeRasterizationPropertiesEXT, PhysicalDeviceCooperativeMatrixFeaturesNV, PhysicalDeviceCooperativeMatrixPropertiesNV, PhysicalDeviceCornerSampledImageFeaturesNV, PhysicalDeviceCoverageReductionModeFeaturesNV, PhysicalDeviceCustomBorderColorFeaturesEXT, PhysicalDeviceCustomBorderColorPropertiesEXT, PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV, PhysicalDeviceDepthClipEnableFeaturesEXT, PhysicalDeviceDepthStencilResolveProperties, PhysicalDeviceDescriptorIndexingFeatures, PhysicalDeviceDescriptorIndexingProperties, PhysicalDeviceDeviceGeneratedCommandsFeaturesNV, PhysicalDeviceDeviceGeneratedCommandsPropertiesNV, PhysicalDeviceDiagnosticsConfigFeaturesNV, PhysicalDeviceDiscardRectanglePropertiesEXT, PhysicalDeviceDriverProperties, PhysicalDeviceExclusiveScissorFeaturesNV, PhysicalDeviceExtendedDynamicStateFeaturesEXT, PhysicalDeviceExternalBufferInfo, PhysicalDeviceExternalFenceInfo, PhysicalDeviceExternalImageFormatInfo, PhysicalDeviceExternalMemoryHostPropertiesEXT, PhysicalDeviceExternalSemaphoreInfo, PhysicalDeviceFeatures2, PhysicalDeviceFloatControlsProperties, PhysicalDeviceFragmentDensityMapFeaturesEXT, PhysicalDeviceFragmentDensityMapPropertiesEXT, PhysicalDeviceFragmentShaderBarycentricFeaturesNV, PhysicalDeviceFragmentShaderInterlockFeaturesEXT, PhysicalDeviceGroupProperties, PhysicalDeviceHostQueryResetFeatures, PhysicalDeviceIDProperties, PhysicalDeviceImageDrmFormatModifierInfoEXT, PhysicalDeviceImageFormatInfo2, PhysicalDeviceImageViewImageFormatInfoEXT, PhysicalDeviceImagelessFramebufferFeatures, PhysicalDeviceIndexTypeUint8FeaturesEXT, PhysicalDeviceInlineUniformBlockFeaturesEXT, PhysicalDeviceInlineUniformBlockPropertiesEXT, PhysicalDeviceLineRasterizationFeaturesEXT, PhysicalDeviceLineRasterizationPropertiesEXT, PhysicalDeviceMaintenance3Properties, PhysicalDeviceMemoryBudgetPropertiesEXT, PhysicalDeviceMemoryPriorityFeaturesEXT, PhysicalDeviceMemoryProperties2, PhysicalDeviceMeshShaderFeaturesNV, PhysicalDeviceMeshShaderPropertiesNV, PhysicalDeviceMultiviewFeatures, PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX, PhysicalDeviceMultiviewProperties, PhysicalDevicePCIBusInfoPropertiesEXT, PhysicalDevicePerformanceQueryFeaturesKHR, PhysicalDevicePerformanceQueryPropertiesKHR, PhysicalDevicePipelineCreationCacheControlFeaturesEXT, PhysicalDevicePipelineExecutablePropertiesFeaturesKHR, PhysicalDevicePointClippingProperties, PhysicalDevicePrivateDataFeaturesEXT, PhysicalDeviceProperties2, PhysicalDeviceProtectedMemoryFeatures, PhysicalDeviceProtectedMemoryProperties, PhysicalDevicePushDescriptorPropertiesKHR, PhysicalDeviceRayTracingFeaturesKHR, PhysicalDeviceRayTracingPropertiesKHR, PhysicalDeviceRayTracingPropertiesNV, PhysicalDeviceRepresentativeFragmentTestFeaturesNV, PhysicalDeviceRobustness2FeaturesEXT, PhysicalDeviceRobustness2PropertiesEXT, PhysicalDeviceSampleLocationsPropertiesEXT, PhysicalDeviceSamplerFilterMinmaxProperties, PhysicalDeviceSamplerYcbcrConversionFeatures, PhysicalDeviceScalarBlockLayoutFeatures, PhysicalDeviceSeparateDepthStencilLayoutsFeatures, PhysicalDeviceShaderAtomicInt64Features, PhysicalDeviceShaderClockFeaturesKHR, PhysicalDeviceShaderCoreProperties2AMD, PhysicalDeviceShaderCorePropertiesAMD, PhysicalDeviceShaderDemoteToHelperInvocationFeaturesEXT, PhysicalDeviceShaderDrawParametersFeatures, PhysicalDeviceShaderFloat16Int8Features, PhysicalDeviceShaderImageFootprintFeaturesNV, PhysicalDeviceShaderIntegerFunctions2FeaturesINTEL, PhysicalDeviceShaderSMBuiltinsFeaturesNV, PhysicalDeviceShaderSMBuiltinsPropertiesNV, PhysicalDeviceShaderSubgroupExtendedTypesFeatures, PhysicalDeviceShadingRateImageFeaturesNV, PhysicalDeviceShadingRateImagePropertiesNV, PhysicalDeviceSparseImageFormatInfo2, PhysicalDeviceSubgroupProperties, PhysicalDeviceSubgroupSizeControlFeaturesEXT, PhysicalDeviceSubgroupSizeControlPropertiesEXT, PhysicalDeviceSurfaceInfo2KHR, PhysicalDeviceTexelBufferAlignmentFeaturesEXT, PhysicalDeviceTexelBufferAlignmentPropertiesEXT, PhysicalDeviceTextureCompressionASTCHDRFeaturesEXT, PhysicalDeviceTimelineSemaphoreFeatures, PhysicalDeviceTimelineSemaphoreProperties, PhysicalDeviceToolPropertiesEXT, PhysicalDeviceTransformFeedbackFeaturesEXT, PhysicalDeviceTransformFeedbackPropertiesEXT, PhysicalDeviceUniformBufferStandardLayoutFeatures, PhysicalDeviceVariablePointersFeatures, PhysicalDeviceVertexAttributeDivisorFeaturesEXT, PhysicalDeviceVertexAttributeDivisorPropertiesEXT, PhysicalDeviceVulkan11Features, PhysicalDeviceVulkan11Properties, PhysicalDeviceVulkan12Features, PhysicalDeviceVulkan12Properties, PhysicalDeviceVulkanMemoryModelFeatures, PhysicalDeviceYcbcrImageArraysFeaturesEXT, PipelineCacheCreateInfo, PipelineColorBlendAdvancedStateCreateInfoEXT, PipelineColorBlendStateCreateInfo, PipelineCompilerControlCreateInfoAMD, PipelineCoverageModulationStateCreateInfoNV, PipelineCoverageReductionStateCreateInfoNV, PipelineCoverageToColorStateCreateInfoNV, PipelineCreationFeedbackCreateInfoEXT, PipelineDepthStencilStateCreateInfo, PipelineDiscardRectangleStateCreateInfoEXT, PipelineDynamicStateCreateInfo, PipelineExecutableInfoKHR, PipelineExecutableInternalRepresentationKHR, PipelineExecutablePropertiesKHR, PipelineExecutableStatisticKHR, PipelineInfoKHR, PipelineInputAssemblyStateCreateInfo, PipelineLayoutCreateInfo, PipelineLibraryCreateInfoKHR, PipelineMultisampleStateCreateInfo, PipelineRasterizationConservativeStateCreateInfoEXT, PipelineRasterizationDepthClipStateCreateInfoEXT, PipelineRasterizationLineStateCreateInfoEXT, PipelineRasterizationStateCreateInfo, PipelineRasterizationStateRasterizationOrderAMD, PipelineRasterizationStateStreamCreateInfoEXT, PipelineRepresentativeFragmentTestStateCreateInfoNV, PipelineSampleLocationsStateCreateInfoEXT, PipelineShaderStageCreateInfo, PipelineShaderStageRequiredSubgroupSizeCreateInfoEXT, PipelineTessellationDomainOriginStateCreateInfo, PipelineTessellationStateCreateInfo, PipelineVertexInputDivisorStateCreateInfoEXT, PipelineVertexInputStateCreateInfo, PipelineViewportCoarseSampleOrderStateCreateInfoNV, PipelineViewportExclusiveScissorStateCreateInfoNV, PipelineViewportShadingRateImageStateCreateInfoNV, PipelineViewportStateCreateInfo, PipelineViewportSwizzleStateCreateInfoNV, PipelineViewportWScalingStateCreateInfoNV, PresentFrameTokenGGP, PresentInfoKHR, PresentRegionsKHR, PresentTimesInfoGOOGLE, PrivateDataSlotCreateInfoEXT, ProtectedSubmitInfo, QueryPoolCreateInfo, QueryPoolPerformanceCreateInfoKHR, QueryPoolPerformanceQueryCreateInfoINTEL, QueueFamilyCheckpointPropertiesNV, QueueFamilyProperties2, RayTracingPipelineCreateInfoKHR, RayTracingPipelineCreateInfoNV, RayTracingPipelineInterfaceCreateInfoKHR, RayTracingShaderGroupCreateInfoKHR, RayTracingShaderGroupCreateInfoNV, RenderPassAttachmentBeginInfo, RenderPassBeginInfo, RenderPassCreateInfo, RenderPassCreateInfo2, RenderPassFragmentDensityMapCreateInfoEXT, RenderPassInputAttachmentAspectCreateInfo, RenderPassMultiviewCreateInfo, RenderPassSampleLocationsBeginInfoEXT, RenderPassTransformBeginInfoQCOM, SampleLocationsInfoEXT, SamplerCreateInfo, SamplerCustomBorderColorCreateInfoEXT, SamplerReductionModeCreateInfo, SamplerYcbcrConversionCreateInfo, SamplerYcbcrConversionImageFormatProperties, SamplerYcbcrConversionInfo, SemaphoreCreateInfo, SemaphoreGetFdInfoKHR, SemaphoreGetWin32HandleInfoKHR, SemaphoreSignalInfo, SemaphoreTypeCreateInfo, SemaphoreWaitInfo, ShaderModuleCreateInfo, ShaderModuleValidationCacheCreateInfoEXT, SharedPresentSurfaceCapabilitiesKHR, SparseImageFormatProperties2, SparseImageMemoryRequirements2, StreamDescriptorSurfaceCreateInfoGGP, SubmitInfo, SubpassBeginInfo, SubpassDependency2, SubpassDescription2, SubpassDescriptionDepthStencilResolve, SubpassEndInfo, SurfaceCapabilities2EXT, SurfaceCapabilities2KHR, SurfaceCapabilitiesFullScreenExclusiveEXT, SurfaceFormat2KHR, SurfaceFullScreenExclusiveInfoEXT, SurfaceFullScreenExclusiveWin32InfoEXT, SurfaceProtectedCapabilitiesKHR, SwapchainCounterCreateInfoEXT, SwapchainCreateInfoKHR, SwapchainDisplayNativeHdrCreateInfoAMD, TextureLODGatherFormatPropertiesAMD, TimelineSemaphoreSubmitInfo, ValidationCacheCreateInfoEXT, ValidationFeaturesEXT, ValidationFlagsEXT, ViSurfaceCreateInfoNN, WaylandSurfaceCreateInfoKHR, Win32KeyedMutexAcquireReleaseInfoKHR, Win32KeyedMutexAcquireReleaseInfoNV, Win32SurfaceCreateInfoKHR, WriteDescriptorSet, WriteDescriptorSetAccelerationStructureKHR, WriteDescriptorSetInlineUniformBlockEXT, XcbSurfaceCreateInfoKHR, XlibSurfaceCreateInfoKHR

Constructors

StructureType Int32 

Bundled Patterns

pattern STRUCTURE_TYPE_BUFFER_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_VIEW_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_INFO :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_POOL_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_COPY_DESCRIPTOR_SET :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_POOL_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_QUEUE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_APPLICATION_INFO :: StructureType 
pattern STRUCTURE_TYPE_INSTANCE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SUBMIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_MAPPED_MEMORY_RANGE :: StructureType 
pattern STRUCTURE_TYPE_BIND_SPARSE_INFO :: StructureType 
pattern STRUCTURE_TYPE_FENCE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EVENT_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SHADER_MODULE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_CACHE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_INPUT_ASSEMBLY_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_TESSELLATION_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_MULTISAMPLE_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_DEPTH_STENCIL_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_DYNAMIC_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_GRAPHICS_PIPELINE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_COMPUTE_PIPELINE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_LAYOUT_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_FRAMEBUFFER_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_MEMORY_BARRIER :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_MEMORY_BARRIER :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_BARRIER :: StructureType 
pattern STRUCTURE_TYPE_LOADER_INSTANCE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_LOADER_DEVICE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_DIAGNOSTICS_CONFIG_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DIAGNOSTICS_CONFIG_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_CREATION_CACHE_CONTROL_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PRIVATE_DATA_SLOT_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_PRIVATE_DATA_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PRIVATE_DATA_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_LIBRARY_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CUSTOM_BORDER_COLOR_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CUSTOM_BORDER_COLOR_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_CUSTOM_BORDER_COLOR_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_ROBUSTNESS_2_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_TRANSFORM_BEGIN_INFO_QCOM :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_RENDER_PASS_TRANSFORM_INFO_QCOM :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXEL_BUFFER_ALIGNMENT_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_GENERATED_COMMANDS_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_GENERATED_COMMANDS_MEMORY_REQUIREMENTS_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_GENERATED_COMMANDS_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_INDIRECT_COMMANDS_LAYOUT_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_INDIRECT_COMMANDS_LAYOUT_TOKEN_NV :: StructureType 
pattern STRUCTURE_TYPE_GRAPHICS_PIPELINE_SHADER_GROUPS_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_GRAPHICS_SHADER_GROUP_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_GENERATED_COMMANDS_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DEMOTE_TO_HELPER_INVOCATION_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INTERNAL_REPRESENTATION_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_EXECUTABLE_STATISTIC_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_EXECUTABLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_EXECUTABLE_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PIPELINE_EXECUTABLE_PROPERTIES_FEATURES_KHR :: StructureType 
pattern STRUCTURE_TYPE_DEFERRED_OPERATION_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTENDED_DYNAMIC_STATE_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_INDEX_TYPE_UINT8_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_LINE_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_LINE_RASTERIZATION_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_HEADLESS_SURFACE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_WIN32_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_CAPABILITIES_FULL_SCREEN_EXCLUSIVE_EXT :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_YCBCR_IMAGE_ARRAYS_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_SHADER_INTERLOCK_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_FRAMEBUFFER_MIXED_SAMPLES_COMBINATION_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COVERAGE_REDUCTION_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COVERAGE_REDUCTION_MODE_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_COOPERATIVE_MATRIX_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COOPERATIVE_MATRIX_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_VALIDATION_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TOOL_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_DEVICE_ADDRESS_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_BUFFER_DEVICE_ADDRESS_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEDICATED_ALLOCATION_IMAGE_ALIASING_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_PROTECTED_CAPABILITIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_PRIORITY_ALLOCATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PRIORITY_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_BUDGET_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COHERENT_MEMORY_FEATURES_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_2_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_SIZE_CONTROL_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_SHADER_STAGE_REQUIRED_SUBGROUP_SIZE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_SIZE_CONTROL_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_FRAGMENT_DENSITY_MAP_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_DENSITY_MAP_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_METAL_SURFACE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGEPIPE_SURFACE_CREATE_INFO_FUCHSIA :: StructureType 
pattern STRUCTURE_TYPE_SWAPCHAIN_DISPLAY_NATIVE_HDR_CREATE_INFO_AMD :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_NATIVE_HDR_SURFACE_CAPABILITIES_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PCI_BUS_INFO_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_INTEGER_FUNCTIONS_2_FEATURES_INTEL :: StructureType 
pattern STRUCTURE_TYPE_QUEUE_FAMILY_CHECKPOINT_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_CHECKPOINT_DATA_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXCLUSIVE_SCISSOR_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_EXCLUSIVE_SCISSOR_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_IMAGE_FOOTPRINT_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FRAGMENT_SHADER_BARYCENTRIC_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MESH_SHADER_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_COMPUTE_SHADER_DERIVATIVES_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_CREATION_FEEDBACK_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PRESENT_FRAME_TOKEN_GGP :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VERTEX_INPUT_DIVISOR_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VERTEX_ATTRIBUTE_DIVISOR_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_MEMORY_OVERALLOCATION_CREATE_INFO_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CORE_PROPERTIES_AMD :: StructureType 
pattern STRUCTURE_TYPE_CALIBRATED_TIMESTAMP_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COMPILER_CONTROL_CREATE_INFO_AMD :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_CLOCK_FEATURES_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_MEMORY_HOST_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_HOST_POINTER_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_MEMORY_HOST_POINTER_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_QUEUE_GLOBAL_PRIORITY_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_FILTER_CUBIC_IMAGE_VIEW_IMAGE_FORMAT_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_VIEW_IMAGE_FORMAT_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_REPRESENTATIVE_FRAGMENT_TEST_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_REPRESENTATIVE_FRAGMENT_TEST_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_SHADER_GROUP_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_GEOMETRY_AABB_NV :: StructureType 
pattern STRUCTURE_TYPE_GEOMETRY_TRIANGLES_NV :: StructureType 
pattern STRUCTURE_TYPE_GEOMETRY_NV :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_PIPELINE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_COARSE_SAMPLE_ORDER_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADING_RATE_IMAGE_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADING_RATE_IMAGE_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_SHADING_RATE_IMAGE_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_SHADER_MODULE_VALIDATION_CACHE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_VALIDATION_CACHE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_EXPLICIT_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_DRM_FORMAT_MODIFIER_LIST_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_DRM_FORMAT_MODIFIER_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_DRM_FORMAT_MODIFIER_PROPERTIES_LIST_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_PROPERTIES_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SM_BUILTINS_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COVERAGE_MODULATION_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_PIPELINE_INTERFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_SHADER_GROUP_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_RAY_TRACING_PIPELINE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_FEATURES_KHR :: StructureType 
pattern STRUCTURE_TYPE_COPY_MEMORY_TO_ACCELERATION_STRUCTURE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_TO_MEMORY_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_VERSION_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_TRIANGLES_DATA_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_INSTANCES_DATA_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_AABBS_DATA_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_DEVICE_ADDRESS_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_GEOMETRY_TYPE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACCELERATION_STRUCTURE_BUILD_GEOMETRY_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET_ACCELERATION_STRUCTURE_KHR :: StructureType 
pattern STRUCTURE_TYPE_BIND_ACCELERATION_STRUCTURE_MEMORY_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COVERAGE_TO_COLOR_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_COLOR_BLEND_ADVANCED_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_BLEND_OPERATION_ADVANCED_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_MULTISAMPLE_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SAMPLE_LOCATIONS_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_SAMPLE_LOCATIONS_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_SAMPLE_LOCATIONS_BEGIN_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_SAMPLE_LOCATIONS_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_POOL_INLINE_UNIFORM_BLOCK_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET_INLINE_UNIFORM_BLOCK_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_INLINE_UNIFORM_BLOCK_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_INLINE_UNIFORM_BLOCK_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_FORMAT_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_GET_ANDROID_HARDWARE_BUFFER_INFO_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_ANDROID_HARDWARE_BUFFER_INFO_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_FORMAT_PROPERTIES_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_PROPERTIES_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_ANDROID_HARDWARE_BUFFER_USAGE_ANDROID :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_MESSENGER_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_MESSENGER_CALLBACK_DATA_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_LABEL_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_OBJECT_TAG_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_UTILS_OBJECT_NAME_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_MACOS_SURFACE_CREATE_INFO_MVK :: StructureType 
pattern STRUCTURE_TYPE_IOS_SURFACE_CREATE_INFO_MVK :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PLANE_CAPABILITIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PLANE_INFO_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_MODE_PROPERTIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PLANE_PROPERTIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PROPERTIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_FORMAT_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_CAPABILITIES_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SURFACE_INFO_2_KHR :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_COUNTER_DESCRIPTION_KHR :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_COUNTER_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACQUIRE_PROFILING_LOCK_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PERFORMANCE_QUERY_SUBMIT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PERFORMANCE_QUERY_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PERFORMANCE_QUERY_FEATURES_KHR :: StructureType 
pattern STRUCTURE_TYPE_FENCE_GET_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_FENCE_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_FENCE_GET_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_FENCE_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_FENCE_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_SHARED_PRESENT_SURFACE_CAPABILITIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_HDR_METADATA_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_DEPTH_CLIP_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_CLIP_ENABLE_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_CONSERVATIVE_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CONSERVATIVE_RASTERIZATION_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_DISCARD_RECTANGLE_STATE_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DISCARD_RECTANGLE_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_SWIZZLE_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PER_VIEW_ATTRIBUTES_PROPERTIES_NVX :: StructureType 
pattern STRUCTURE_TYPE_PRESENT_TIMES_INFO_GOOGLE :: StructureType 
pattern STRUCTURE_TYPE_SWAPCHAIN_COUNTER_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_EVENT_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_EVENT_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_POWER_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_SURFACE_CAPABILITIES_2_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_VIEWPORT_W_SCALING_STATE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PRESENT_REGIONS_KHR :: StructureType 
pattern STRUCTURE_TYPE_CONDITIONAL_RENDERING_BEGIN_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CONDITIONAL_RENDERING_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_COMMAND_BUFFER_INHERITANCE_CONDITIONAL_RENDERING_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PUSH_DESCRIPTOR_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_GET_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_SEMAPHORE_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_GET_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_D3D12_FENCE_SUBMIT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_SEMAPHORE_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_SEMAPHORE_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_GET_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_FD_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_MEMORY_FD_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_GET_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_WIN32_HANDLE_PROPERTIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_ASTC_DECODE_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_ASTC_DECODE_MODE_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TEXTURE_COMPRESSION_ASTC_HDR_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_VI_SURFACE_CREATE_INFO_NN :: StructureType 
pattern STRUCTURE_TYPE_VALIDATION_FLAGS_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_SWAPCHAIN_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ACQUIRE_NEXT_IMAGE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_BIND_IMAGE_MEMORY_SWAPCHAIN_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_SWAPCHAIN_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_PRESENT_CAPABILITIES_KHR :: StructureType 
pattern STRUCTURE_TYPE_WIN32_KEYED_MUTEX_ACQUIRE_RELEASE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_MEMORY_WIN32_HANDLE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_IMPORT_MEMORY_WIN32_HANDLE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_CORNER_SAMPLED_IMAGE_FEATURES_NV :: StructureType 
pattern STRUCTURE_TYPE_STREAM_DESCRIPTOR_SURFACE_CREATE_INFO_GGP :: StructureType 
pattern STRUCTURE_TYPE_TEXTURE_LOD_GATHER_FORMAT_PROPERTIES_AMD :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_ADDRESS_PROPERTIES_NVX :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_HANDLE_INFO_NVX :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_STREAM_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TRANSFORM_FEEDBACK_PROPERTIES_EXT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TRANSFORM_FEEDBACK_FEATURES_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEDICATED_ALLOCATION_MEMORY_ALLOCATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_DEDICATED_ALLOCATION_BUFFER_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_DEDICATED_ALLOCATION_IMAGE_CREATE_INFO_NV :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_MARKER_MARKER_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_TAG_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_NAME_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_RASTERIZATION_STATE_RASTERIZATION_ORDER_AMD :: StructureType 
pattern STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT :: StructureType 
pattern STRUCTURE_TYPE_WIN32_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_ANDROID_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_WAYLAND_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_XCB_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_XLIB_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_PRESENT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_SURFACE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DISPLAY_MODE_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_PRESENT_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_SWAPCHAIN_CREATE_INFO_KHR :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_MEMORY_OPAQUE_CAPTURE_ADDRESS_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_OPAQUE_CAPTURE_ADDRESS_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_OPAQUE_CAPTURE_ADDRESS_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_DEVICE_ADDRESS_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_BUFFER_DEVICE_ADDRESS_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_SIGNAL_INFO :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_WAIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_TIMELINE_SEMAPHORE_SUBMIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_SEMAPHORE_TYPE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TIMELINE_SEMAPHORE_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_TIMELINE_SEMAPHORE_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_HOST_QUERY_RESET_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_STENCIL_LAYOUT :: StructureType 
pattern STRUCTURE_TYPE_ATTACHMENT_REFERENCE_STENCIL_LAYOUT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SEPARATE_DEPTH_STENCIL_LAYOUTS_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_SUBGROUP_EXTENDED_TYPES_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_UNIFORM_BUFFER_STANDARD_LAYOUT_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_ATTACHMENT_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENT_IMAGE_INFO :: StructureType 
pattern STRUCTURE_TYPE_FRAMEBUFFER_ATTACHMENTS_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGELESS_FRAMEBUFFER_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_MEMORY_MODEL_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_REDUCTION_MODE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SAMPLER_FILTER_MINMAX_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_STENCIL_USAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SCALAR_BLOCK_LAYOUT_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_DESCRIPTION_DEPTH_STENCIL_RESOLVE :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DEPTH_STENCIL_RESOLVE_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_LAYOUT_SUPPORT :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_VARIABLE_DESCRIPTOR_COUNT_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DESCRIPTOR_INDEXING_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_BINDING_FLAGS_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FLOAT_CONTROLS_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_FLOAT16_INT8_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_ATOMIC_INT64_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_DRIVER_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_8BIT_STORAGE_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_END_INFO :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_DEPENDENCY_2 :: StructureType 
pattern STRUCTURE_TYPE_SUBPASS_DESCRIPTION_2 :: StructureType 
pattern STRUCTURE_TYPE_ATTACHMENT_REFERENCE_2 :: StructureType 
pattern STRUCTURE_TYPE_ATTACHMENT_DESCRIPTION_2 :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_FORMAT_LIST_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_2_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VULKAN_1_1_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SHADER_DRAW_PARAMETERS_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_SET_LAYOUT_SUPPORT :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MAINTENANCE_3_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_SEMAPHORE_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_SEMAPHORE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_SEMAPHORE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_FENCE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_FENCE_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_FENCE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXPORT_MEMORY_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_MEMORY_IMAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_MEMORY_BUFFER_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_ID_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_BUFFER_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_BUFFER_INFO :: StructureType 
pattern STRUCTURE_TYPE_EXTERNAL_IMAGE_FORMAT_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_EXTERNAL_IMAGE_FORMAT_INFO :: StructureType 
pattern STRUCTURE_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_YCBCR_CONVERSION_IMAGE_FORMAT_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SAMPLER_YCBCR_CONVERSION_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_PLANE_MEMORY_REQUIREMENTS_INFO :: StructureType 
pattern STRUCTURE_TYPE_BIND_IMAGE_PLANE_MEMORY_INFO :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_YCBCR_CONVERSION_INFO :: StructureType 
pattern STRUCTURE_TYPE_SAMPLER_YCBCR_CONVERSION_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_QUEUE_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PROTECTED_MEMORY_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PROTECTED_MEMORY_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PROTECTED_SUBMIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_VARIABLE_POINTERS_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MULTIVIEW_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_MULTIVIEW_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PIPELINE_TESSELLATION_DOMAIN_ORIGIN_STATE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_VIEW_USAGE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_RENDER_PASS_INPUT_ATTACHMENT_ASPECT_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_POINT_CLIPPING_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SPARSE_IMAGE_FORMAT_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_SPARSE_IMAGE_FORMAT_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_QUEUE_FAMILY_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_FORMAT_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_FORMAT_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_FORMAT_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_PROPERTIES_2 :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_FEATURES_2 :: StructureType 
pattern STRUCTURE_TYPE_SPARSE_IMAGE_MEMORY_REQUIREMENTS_2 :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_REQUIREMENTS_2 :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_SPARSE_MEMORY_REQUIREMENTS_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_IMAGE_MEMORY_REQUIREMENTS_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_BUFFER_MEMORY_REQUIREMENTS_INFO_2 :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_DEVICE_CREATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_GROUP_PROPERTIES :: StructureType 
pattern STRUCTURE_TYPE_BIND_IMAGE_MEMORY_DEVICE_GROUP_INFO :: StructureType 
pattern STRUCTURE_TYPE_BIND_BUFFER_MEMORY_DEVICE_GROUP_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_DEDICATED_ALLOCATE_INFO :: StructureType 
pattern STRUCTURE_TYPE_MEMORY_DEDICATED_REQUIREMENTS :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_16BIT_STORAGE_FEATURES :: StructureType 
pattern STRUCTURE_TYPE_BIND_IMAGE_MEMORY_INFO :: StructureType 
pattern STRUCTURE_TYPE_BIND_BUFFER_MEMORY_INFO :: StructureType 
pattern STRUCTURE_TYPE_PHYSICAL_DEVICE_SUBGROUP_PROPERTIES :: StructureType 

Instances

Instances details
Eq StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Ord StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Read StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Show StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Storable StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType

Zero StructureType Source # 
Instance details

Defined in Vulkan.Core10.Enums.StructureType