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

Vulkan.Core10.Pass

Synopsis

Documentation

createFramebuffer Source #

Arguments

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

device is the logical device that creates the framebuffer.

-> FramebufferCreateInfo a

pCreateInfo is a pointer to a FramebufferCreateInfo structure describing additional information about framebuffer creation.

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

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

-> io Framebuffer 

vkCreateFramebuffer - Create a new framebuffer object

Valid Usage

  • If pCreateInfo->flags does not include FRAMEBUFFER_CREATE_IMAGELESS_BIT, and attachmentCount is not 0, each element of pCreateInfo->pAttachments must have been created on device

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, Framebuffer, FramebufferCreateInfo

withFramebuffer :: forall a io r. (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => Device -> FramebufferCreateInfo a -> Maybe AllocationCallbacks -> (io Framebuffer -> (Framebuffer -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createFramebuffer and destroyFramebuffer

To ensure that destroyFramebuffer 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.

destroyFramebuffer Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the framebuffer.

-> Framebuffer

framebuffer is the handle of the framebuffer to destroy.

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

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

-> io () 

vkDestroyFramebuffer - Destroy a framebuffer object

Valid Usage

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

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If framebuffer is not NULL_HANDLE, framebuffer must be a valid Framebuffer handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • If framebuffer is a valid handle, it must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to framebuffer must be externally synchronized

See Also

AllocationCallbacks, Device, Framebuffer

createRenderPass Source #

Arguments

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

device is the logical device that creates the render pass.

-> RenderPassCreateInfo a

pCreateInfo is a pointer to a RenderPassCreateInfo 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 

vkCreateRenderPass - Create a new render pass object

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, RenderPass, RenderPassCreateInfo

withRenderPass :: forall a io r. (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo a -> Maybe AllocationCallbacks -> (io RenderPass -> (RenderPass -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createRenderPass and destroyRenderPass

To ensure that destroyRenderPass 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.

destroyRenderPass Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the render pass.

-> RenderPass

renderPass is the handle of the render pass to destroy.

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

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

-> io () 

vkDestroyRenderPass - Destroy a render pass object

Valid Usage

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

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If renderPass is not NULL_HANDLE, renderPass must be a valid RenderPass handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • If renderPass is a valid handle, it must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to renderPass must be externally synchronized

See Also

AllocationCallbacks, Device, RenderPass

getRenderAreaGranularity Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the render pass.

-> RenderPass

renderPass is a handle to a render pass.

-> io ("granularity" ::: Extent2D) 

vkGetRenderAreaGranularity - Returns the granularity for optimal render area

Description

The conditions leading to an optimal renderArea are:

  • the offset.x member in renderArea is a multiple of the width member of the returned Extent2D (the horizontal granularity).
  • the offset.y member in renderArea is a multiple of the height of the returned Extent2D (the vertical granularity).
  • either the offset.width member in renderArea is a multiple of the horizontal granularity or offset.x+offset.width is equal to the width of the framebuffer in the RenderPassBeginInfo.
  • either the offset.height member in renderArea is a multiple of the vertical granularity or offset.y+offset.height is equal to the height of the framebuffer in the RenderPassBeginInfo.

Subpass dependencies are not affected by the render area, and apply to the entire image subresources attached to the framebuffer as specified in the description of automatic layout transitions. Similarly, pipeline barriers are valid even if their effect extends outside the render area.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • renderPass must be a valid RenderPass handle
  • pGranularity must be a valid pointer to a Extent2D structure
  • renderPass must have been created, allocated, or retrieved from device

See Also

Device, Extent2D, RenderPass

data AttachmentDescription Source #

VkAttachmentDescription - Structure specifying an attachment description

Description

If the attachment uses a color format, then loadOp and storeOp are used, and stencilLoadOp and stencilStoreOp are ignored. If the format has depth and/or stencil components, loadOp and storeOp apply only to the depth data, while stencilLoadOp and stencilStoreOp define how the stencil data is handled. loadOp and stencilLoadOp define the load operations that execute as part of the first subpass that uses the attachment. storeOp and stencilStoreOp define the store operations that execute as part of the last subpass that uses the attachment.

The load operation for each sample in an attachment happens-before any recorded command which accesses the sample in the first subpass where the attachment is used. Load operations for attachments with a depth/stencil format execute in the PIPELINE_STAGE_EARLY_FRAGMENT_TESTS_BIT pipeline stage. Load operations for attachments with a color format execute in the PIPELINE_STAGE_COLOR_ATTACHMENT_OUTPUT_BIT pipeline stage.

The store operation for each sample in an attachment happens-after any recorded command which accesses the sample in the last subpass where the attachment is used. Store operations for attachments with a depth/stencil format execute in the PIPELINE_STAGE_LATE_FRAGMENT_TESTS_BIT pipeline stage. Store operations for attachments with a color format execute in the PIPELINE_STAGE_COLOR_ATTACHMENT_OUTPUT_BIT pipeline stage.

If an attachment is not used by any subpass, then loadOp, storeOp, stencilStoreOp, and stencilLoadOp are ignored, and the attachment’s memory contents will not be modified by execution of a render pass instance.

The load and store operations apply on the first and last use of each view in the render pass, respectively. If a view index of an attachment is not included in the view mask in any subpass that uses it, then the load and store operations are ignored, and the attachment’s memory contents will not be modified by execution of a render pass instance.

During a render pass instance, input/color attachments with color formats that have a component size of 8, 16, or 32 bits must be represented in the attachment’s format throughout the instance. Attachments with other floating- or fixed-point color formats, or with depth components may be represented in a format with a precision higher than the attachment format, but must be represented with the same range. When such a component is loaded via the loadOp, it will be converted into an implementation-dependent format used by the render pass. Such components must be converted from the render pass format, to the format of the attachment, before they are resolved or stored at the end of a render pass instance via storeOp. Conversions occur as described in Numeric Representation and Computation and Fixed-Point Data Conversions.

If flags includes ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT, then the attachment is treated as if it shares physical memory with another attachment in the same render pass. This information limits the ability of the implementation to reorder certain operations (like layout transitions and the loadOp) such that it is not improperly reordered against other uses of the same physical memory via a different attachment. This is described in more detail below.

If a render pass uses multiple attachments that alias the same device memory, those attachments must each include the ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT bit in their attachment description flags. Attachments aliasing the same memory occurs in multiple ways:

  • Multiple attachments being assigned the same image view as part of framebuffer creation.
  • Attachments using distinct image views that correspond to the same image subresource of an image.
  • Attachments using views of distinct image subresources which are bound to overlapping memory ranges.

Note

Render passes must include subpass dependencies (either directly or via a subpass dependency chain) between any two subpasses that operate on the same attachment or aliasing attachments and those subpass dependencies must include execution and memory dependencies separating uses of the aliases, if at least one of those subpasses writes to one of the aliases. These dependencies must not include the DEPENDENCY_BY_REGION_BIT if the aliases are views of distinct image subresources which overlap in memory.

Multiple attachments that alias the same memory must not be used in a single subpass. A given attachment index must not be used multiple times in a single subpass, with one exception: two subpass attachments can use the same attachment index if at least one use is as an input attachment and neither use is as a resolve or preserve attachment. In other words, the same view can be used simultaneously as an input and color or depth/stencil attachment, but must not be used as multiple color or depth/stencil attachments nor as resolve or preserve attachments. The precise set of valid scenarios is described in more detail below.

If a set of attachments alias each other, then all except the first to be used in the render pass must use an initialLayout of IMAGE_LAYOUT_UNDEFINED, since the earlier uses of the other aliases make their contents undefined. Once an alias has been used and a different alias has been used after it, the first alias must not be used in any later subpasses. However, an application can assign the same image view to multiple aliasing attachment indices, which allows that image view to be used multiple times even if other aliases are used in between.

Note

Once an attachment needs the ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT bit, there should be no additional cost of introducing additional aliases, and using these additional aliases may allow more efficient clearing of the attachments on multiple uses via ATTACHMENT_LOAD_OP_CLEAR.

Valid Usage

Valid Usage (Implicit)

See Also

AttachmentDescriptionFlags, AttachmentLoadOp, AttachmentStoreOp, Format, ImageLayout, RenderPassCreateInfo, SampleCountFlagBits

Constructors

AttachmentDescription 

Fields

Instances

Instances details
Eq AttachmentDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

Show AttachmentDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

Generic AttachmentDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

Associated Types

type Rep AttachmentDescription :: Type -> Type #

Storable AttachmentDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

FromCStruct AttachmentDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

ToCStruct AttachmentDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

Zero AttachmentDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

type Rep AttachmentDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

data AttachmentReference Source #

Constructors

AttachmentReference 

Fields

Instances

Instances details
Eq AttachmentReference Source # 
Instance details

Defined in Vulkan.Core10.Pass

Show AttachmentReference Source # 
Instance details

Defined in Vulkan.Core10.Pass

Generic AttachmentReference Source # 
Instance details

Defined in Vulkan.Core10.Pass

Associated Types

type Rep AttachmentReference :: Type -> Type #

Storable AttachmentReference Source # 
Instance details

Defined in Vulkan.Core10.Pass

FromCStruct AttachmentReference Source # 
Instance details

Defined in Vulkan.Core10.Pass

ToCStruct AttachmentReference Source # 
Instance details

Defined in Vulkan.Core10.Pass

Zero AttachmentReference Source # 
Instance details

Defined in Vulkan.Core10.Pass

type Rep AttachmentReference Source # 
Instance details

Defined in Vulkan.Core10.Pass

type Rep AttachmentReference = D1 ('MetaData "AttachmentReference" "Vulkan.Core10.Pass" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "AttachmentReference" 'PrefixI 'True) (S1 ('MetaSel ('Just "attachment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "layout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageLayout)))

data SubpassDescription Source #

VkSubpassDescription - Structure specifying a subpass description

Description

Each element of the pInputAttachments array corresponds to an input attachment index in a fragment shader, i.e. if a shader declares an image variable decorated with a InputAttachmentIndex value of X, then it uses the attachment provided in pInputAttachments[X]. Input attachments must also be bound to the pipeline in a descriptor set. If the attachment member of any element of pInputAttachments is ATTACHMENT_UNUSED, the application must not read from the corresponding input attachment index. Fragment shaders can use subpass input variables to access the contents of an input attachment at the fragment’s (x, y, layer) framebuffer coordinates. Input attachments must not be used by any subpasses within a renderpass that enables render pass transform.

Each element of the pColorAttachments array corresponds to an output location in the shader, i.e. if the shader declares an output variable decorated with a Location value of X, then it uses the attachment provided in pColorAttachments[X]. If the attachment member of any element of pColorAttachments is ATTACHMENT_UNUSED, writes to the corresponding location by a fragment are discarded.

If flags does not include SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM, and if pResolveAttachments is not NULL, each of its elements corresponds to a color attachment (the element in pColorAttachments at the same index), and a multisample resolve operation is defined for each attachment. At the end of each subpass, multisample resolve operations read the subpass’s color attachments, and resolve the samples for each pixel within the render area to the same pixel location in the corresponding resolve attachments, unless the resolve attachment index is ATTACHMENT_UNUSED.

Similarly, if flags does not include SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM, and SubpassDescriptionDepthStencilResolve::pDepthStencilResolveAttachment is not NULL and does not have the value ATTACHMENT_UNUSED, it corresponds to the depth/stencil attachment in pDepthStencilAttachment, and multisample resolve operations for depth and stencil are defined by SubpassDescriptionDepthStencilResolve::depthResolveMode and SubpassDescriptionDepthStencilResolve::stencilResolveMode, respectively. At the end of each subpass, multisample resolve operations read the subpass’s depth/stencil attachment, and resolve the samples for each pixel to the same pixel location in the corresponding resolve attachment. If SubpassDescriptionDepthStencilResolve::depthResolveMode is RESOLVE_MODE_NONE, then the depth component of the resolve attachment is not written to and its contents are preserved. Similarly, if SubpassDescriptionDepthStencilResolve::stencilResolveMode is RESOLVE_MODE_NONE, then the stencil component of the resolve attachment is not written to and its contents are preserved. SubpassDescriptionDepthStencilResolve::depthResolveMode is ignored if the Format of the pDepthStencilResolveAttachment does not have a depth component. Similarly, SubpassDescriptionDepthStencilResolve::stencilResolveMode is ignored if the Format of the pDepthStencilResolveAttachment does not have a stencil component.

If the image subresource range referenced by the depth/stencil attachment is created with IMAGE_CREATE_SAMPLE_LOCATIONS_COMPATIBLE_DEPTH_BIT_EXT, then the multisample resolve operation uses the sample locations state specified in the sampleLocationsInfo member of the element of the RenderPassSampleLocationsBeginInfoEXT::pPostSubpassSampleLocations for the subpass.

If pDepthStencilAttachment is NULL, or if its attachment index is ATTACHMENT_UNUSED, it indicates that no depth/stencil attachment will be used in the subpass.

The contents of an attachment within the render area become undefined at the start of a subpass S if all of the following conditions are true:

  • The attachment is used as a color, depth/stencil, or resolve attachment in any subpass in the render pass.
  • There is a subpass S1 that uses or preserves the attachment, and a subpass dependency from S1 to S.
  • The attachment is not used or preserved in subpass S.

In addition, the contents of an attachment within the render area become undefined at the start of a subpass S if all of the following conditions are true:

Once the contents of an attachment become undefined in subpass S, they remain undefined for subpasses in subpass dependency chains starting with subpass S until they are written again. However, they remain valid for subpasses in other subpass dependency chains starting with subpass S1 if those subpasses use or preserve the attachment.

Valid Usage

Valid Usage (Implicit)

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

See Also

AttachmentReference, PipelineBindPoint, RenderPassCreateInfo, SubpassDescriptionFlags

Constructors

SubpassDescription 

Fields

Instances

Instances details
Show SubpassDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

Generic SubpassDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

Associated Types

type Rep SubpassDescription :: Type -> Type #

FromCStruct SubpassDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

ToCStruct SubpassDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

Zero SubpassDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

type Rep SubpassDescription Source # 
Instance details

Defined in Vulkan.Core10.Pass

data SubpassDependency Source #

VkSubpassDependency - Structure specifying a subpass dependency

Description

If srcSubpass is equal to dstSubpass then the SubpassDependency describes a subpass self-dependency, and only constrains the pipeline barriers allowed within a subpass instance. Otherwise, when a render pass instance which includes a subpass dependency is submitted to a queue, it defines a memory dependency between the subpasses identified by srcSubpass and dstSubpass.

If srcSubpass is equal to SUBPASS_EXTERNAL, the first synchronization scope includes commands that occur earlier in submission order than the cmdBeginRenderPass used to begin the render pass instance. Otherwise, the first set of commands includes all commands submitted as part of the subpass instance identified by srcSubpass and any load, store or multisample resolve operations on attachments used in srcSubpass. In either case, the first synchronization scope is limited to operations on the pipeline stages determined by the source stage mask specified by srcStageMask.

If dstSubpass is equal to SUBPASS_EXTERNAL, the second synchronization scope includes commands that occur later in submission order than the cmdEndRenderPass used to end the render pass instance. Otherwise, the second set of commands includes all commands submitted as part of the subpass instance identified by dstSubpass and any load, store or multisample resolve operations on attachments used in dstSubpass. In either case, the second synchronization scope is limited to operations on the pipeline stages determined by the destination stage mask specified by dstStageMask.

The first access scope is limited to access in the pipeline stages determined by the source stage mask specified by srcStageMask. It is also limited to access types in the source access mask specified by srcAccessMask.

The second access scope is limited to access in the pipeline stages determined by the destination stage mask specified by dstStageMask. It is also limited to access types in the destination access mask specified by dstAccessMask.

The availability and visibility operations defined by a subpass dependency affect the execution of image layout transitions within the render pass.

Note

For non-attachment resources, the memory dependency expressed by subpass dependency is nearly identical to that of a MemoryBarrier (with matching srcAccessMask and dstAccessMask parameters) submitted as a part of a cmdPipelineBarrier (with matching srcStageMask and dstStageMask parameters). The only difference being that its scopes are limited to the identified subpasses rather than potentially affecting everything before and after.

For attachments however, subpass dependencies work more like a ImageMemoryBarrier defined similarly to the MemoryBarrier above, the queue family indices set to QUEUE_FAMILY_IGNORED, and layouts as follows:

  • The equivalent to oldLayout is the attachment’s layout according to the subpass description for srcSubpass.
  • The equivalent to newLayout is the attachment’s layout according to the subpass description for dstSubpass.

Valid Usage

Valid Usage (Implicit)

See Also

AccessFlags, DependencyFlags, PipelineStageFlags, RenderPassCreateInfo

Constructors

SubpassDependency 

Fields

Instances

Instances details
Eq SubpassDependency Source # 
Instance details

Defined in Vulkan.Core10.Pass

Show SubpassDependency Source # 
Instance details

Defined in Vulkan.Core10.Pass

Generic SubpassDependency Source # 
Instance details

Defined in Vulkan.Core10.Pass

Associated Types

type Rep SubpassDependency :: Type -> Type #

Storable SubpassDependency Source # 
Instance details

Defined in Vulkan.Core10.Pass

FromCStruct SubpassDependency Source # 
Instance details

Defined in Vulkan.Core10.Pass

ToCStruct SubpassDependency Source # 
Instance details

Defined in Vulkan.Core10.Pass

Zero SubpassDependency Source # 
Instance details

Defined in Vulkan.Core10.Pass

type Rep SubpassDependency Source # 
Instance details

Defined in Vulkan.Core10.Pass

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

VkRenderPassCreateInfo - Structure specifying parameters of a newly created render pass

Description

Note

Care should be taken to avoid a data race here; if any subpasses access attachments with overlapping memory locations, and one of those accesses is a write, a subpass dependency needs to be included between them.

Valid Usage

  • If the attachment member of any element of pInputAttachments, pColorAttachments, pResolveAttachments or pDepthStencilAttachment, or any element of pPreserveAttachments in any element of pSubpasses is not ATTACHMENT_UNUSED, it must be less than attachmentCount

Valid Usage (Implicit)

See Also

AttachmentDescription, RenderPassCreateFlags, StructureType, SubpassDependency, SubpassDescription, createRenderPass

Constructors

RenderPassCreateInfo 

Fields

Instances

Instances details
Extensible RenderPassCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pass

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.Pass

Generic (RenderPassCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pass

Associated Types

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

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

Defined in Vulkan.Core10.Pass

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

Defined in Vulkan.Core10.Pass

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

Defined in Vulkan.Core10.Pass

type Rep (RenderPassCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pass

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

VkFramebufferCreateInfo - Structure specifying parameters of a newly created framebuffer

Description

Applications must ensure that all accesses to memory that backs image subresources used as attachments in a given renderpass instance either happen-before the load operations for those attachments, or happen-after the store operations for those attachments.

For depth/stencil attachments, each aspect can be used separately as attachments and non-attachments as long as the non-attachment accesses are also via an image subresource in either the IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL layout or the IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL layout, and the attachment resource uses whichever of those two layouts the image accesses do not. Use of non-attachment aspects in this case is only well defined if the attachment is used in the subpass where the non-attachment access is being made, or the layout of the image subresource is constant throughout the entire render pass instance, including the initialLayout and finalLayout.

Note

These restrictions mean that the render pass has full knowledge of all uses of all of the attachments, so that the implementation is able to make correct decisions about when and how to perform layout transitions, when to overlap execution of subpasses, etc.

It is legal for a subpass to use no color or depth/stencil attachments, either because it has no attachment references or because all of them are ATTACHMENT_UNUSED. This kind of subpass can use shader side effects such as image stores and atomics to produce an output. In this case, the subpass continues to use the width, height, and layers of the framebuffer to define the dimensions of the rendering area, and the rasterizationSamples from each pipeline’s PipelineMultisampleStateCreateInfo to define the number of samples used in rasterization; however, if PhysicalDeviceFeatures::variableMultisampleRate is FALSE, then all pipelines to be bound with the subpass must have the same value for PipelineMultisampleStateCreateInfo::rasterizationSamples.

Valid Usage

  • attachmentCount must be equal to the attachment count specified in renderPass

Valid Usage (Implicit)

  • pNext must be NULL or a pointer to a valid instance of FramebufferAttachmentsCreateInfo
  • The sType value of each struct in the pNext chain must be unique
  • flags must be a valid combination of FramebufferCreateFlagBits values
  • renderPass must be a valid RenderPass handle
  • Both of renderPass, and the elements of pAttachments that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Device

See Also

FramebufferCreateFlags, ImageView, RenderPass, StructureType, createFramebuffer

Constructors

FramebufferCreateInfo 

Fields

Instances

Instances details
Extensible FramebufferCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Pass

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.Pass

Generic (FramebufferCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pass

Associated Types

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

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

Defined in Vulkan.Core10.Pass

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

Defined in Vulkan.Core10.Pass

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

Defined in Vulkan.Core10.Pass

type Rep (FramebufferCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Pass