| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Vulkan.Core10.Pass
Synopsis
- createFramebuffer :: forall a io. (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => Device -> FramebufferCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io Framebuffer
- withFramebuffer :: forall a io r. (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) => Device -> FramebufferCreateInfo a -> Maybe AllocationCallbacks -> (io Framebuffer -> (Framebuffer -> io ()) -> r) -> r
- destroyFramebuffer :: forall io. MonadIO io => Device -> Framebuffer -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
- createRenderPass :: forall a io. (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io RenderPass
- withRenderPass :: forall a io r. (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) => Device -> RenderPassCreateInfo a -> Maybe AllocationCallbacks -> (io RenderPass -> (RenderPass -> io ()) -> r) -> r
- destroyRenderPass :: forall io. MonadIO io => Device -> RenderPass -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
- getRenderAreaGranularity :: forall io. MonadIO io => Device -> RenderPass -> io ("granularity" ::: Extent2D)
- data AttachmentDescription = AttachmentDescription {}
- data AttachmentReference = AttachmentReference {}
- data SubpassDescription = SubpassDescription {}
- data SubpassDependency = SubpassDependency {}
- data RenderPassCreateInfo (es :: [Type]) = RenderPassCreateInfo {}
- data FramebufferCreateInfo (es :: [Type]) = FramebufferCreateInfo {- next :: Chain es
- flags :: FramebufferCreateFlags
- renderPass :: RenderPass
- attachments :: Vector ImageView
- width :: Word32
- height :: Word32
- layers :: Word32
 
- newtype Framebuffer = Framebuffer Word64
- newtype RenderPass = RenderPass Word64
- newtype AttachmentLoadOp where- AttachmentLoadOp Int32
- pattern ATTACHMENT_LOAD_OP_LOAD :: AttachmentLoadOp
- pattern ATTACHMENT_LOAD_OP_CLEAR :: AttachmentLoadOp
- pattern ATTACHMENT_LOAD_OP_DONT_CARE :: AttachmentLoadOp
 
- newtype AttachmentStoreOp where
- newtype PipelineBindPoint where
- newtype RenderPassCreateFlagBits where
- type RenderPassCreateFlags = RenderPassCreateFlagBits
- newtype AccessFlagBits where- AccessFlagBits Flags
- pattern ACCESS_INDIRECT_COMMAND_READ_BIT :: AccessFlagBits
- pattern ACCESS_INDEX_READ_BIT :: AccessFlagBits
- pattern ACCESS_VERTEX_ATTRIBUTE_READ_BIT :: AccessFlagBits
- pattern ACCESS_UNIFORM_READ_BIT :: AccessFlagBits
- pattern ACCESS_INPUT_ATTACHMENT_READ_BIT :: AccessFlagBits
- pattern ACCESS_SHADER_READ_BIT :: AccessFlagBits
- pattern ACCESS_SHADER_WRITE_BIT :: AccessFlagBits
- pattern ACCESS_COLOR_ATTACHMENT_READ_BIT :: AccessFlagBits
- pattern ACCESS_COLOR_ATTACHMENT_WRITE_BIT :: AccessFlagBits
- pattern ACCESS_DEPTH_STENCIL_ATTACHMENT_READ_BIT :: AccessFlagBits
- pattern ACCESS_DEPTH_STENCIL_ATTACHMENT_WRITE_BIT :: AccessFlagBits
- pattern ACCESS_TRANSFER_READ_BIT :: AccessFlagBits
- pattern ACCESS_TRANSFER_WRITE_BIT :: AccessFlagBits
- pattern ACCESS_HOST_READ_BIT :: AccessFlagBits
- pattern ACCESS_HOST_WRITE_BIT :: AccessFlagBits
- pattern ACCESS_MEMORY_READ_BIT :: AccessFlagBits
- pattern ACCESS_MEMORY_WRITE_BIT :: AccessFlagBits
- pattern ACCESS_COMMAND_PREPROCESS_WRITE_BIT_NV :: AccessFlagBits
- pattern ACCESS_COMMAND_PREPROCESS_READ_BIT_NV :: AccessFlagBits
- pattern ACCESS_FRAGMENT_DENSITY_MAP_READ_BIT_EXT :: AccessFlagBits
- pattern ACCESS_SHADING_RATE_IMAGE_READ_BIT_NV :: AccessFlagBits
- pattern ACCESS_ACCELERATION_STRUCTURE_WRITE_BIT_KHR :: AccessFlagBits
- pattern ACCESS_ACCELERATION_STRUCTURE_READ_BIT_KHR :: AccessFlagBits
- pattern ACCESS_COLOR_ATTACHMENT_READ_NONCOHERENT_BIT_EXT :: AccessFlagBits
- pattern ACCESS_CONDITIONAL_RENDERING_READ_BIT_EXT :: AccessFlagBits
- pattern ACCESS_TRANSFORM_FEEDBACK_COUNTER_WRITE_BIT_EXT :: AccessFlagBits
- pattern ACCESS_TRANSFORM_FEEDBACK_COUNTER_READ_BIT_EXT :: AccessFlagBits
- pattern ACCESS_TRANSFORM_FEEDBACK_WRITE_BIT_EXT :: AccessFlagBits
 
- type AccessFlags = AccessFlagBits
- newtype AttachmentDescriptionFlagBits where
- type AttachmentDescriptionFlags = AttachmentDescriptionFlagBits
- newtype DependencyFlagBits where
- type DependencyFlags = DependencyFlagBits
- newtype SubpassDescriptionFlagBits where- SubpassDescriptionFlagBits Flags
- pattern SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM :: SubpassDescriptionFlagBits
- pattern SUBPASS_DESCRIPTION_FRAGMENT_REGION_BIT_QCOM :: SubpassDescriptionFlagBits
- pattern SUBPASS_DESCRIPTION_PER_VIEW_POSITION_X_ONLY_BIT_NVX :: SubpassDescriptionFlagBits
- pattern SUBPASS_DESCRIPTION_PER_VIEW_ATTRIBUTES_BIT_NVX :: SubpassDescriptionFlagBits
 
- type SubpassDescriptionFlags = SubpassDescriptionFlagBits
- newtype FramebufferCreateFlagBits where
- type FramebufferCreateFlags = FramebufferCreateFlagBits
Documentation
Arguments
| :: forall a io. (Extendss FramebufferCreateInfo a, PokeChain a, MonadIO io) | |
| => Device | 
 | 
| -> FramebufferCreateInfo a | 
 | 
| -> ("allocator" ::: Maybe AllocationCallbacks) | 
 | 
| -> io Framebuffer | 
vkCreateFramebuffer - Create a new framebuffer object
Valid Usage
- If pCreateInfo->flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, andattachmentCountis not0, each element ofpCreateInfo->pAttachmentsmust have been created ondevice
Valid Usage (Implicit)
- devicemust be a valid- Devicehandle
- pCreateInfomust be a valid pointer to a valid- FramebufferCreateInfostructure
- If pAllocatoris notNULL,pAllocatormust be a valid pointer to a validAllocationCallbacksstructure
- pFramebuffermust be a valid pointer to a- Framebufferhandle
Return Codes
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.
Arguments
| :: forall io. MonadIO io | |
| => Device | 
 | 
| -> Framebuffer | 
 | 
| -> ("allocator" ::: Maybe AllocationCallbacks) | 
 | 
| -> io () | 
vkDestroyFramebuffer - Destroy a framebuffer object
Valid Usage
- All submitted commands that refer to framebuffermust have completed execution
- If AllocationCallbackswere provided whenframebufferwas created, a compatible set of callbacks must be provided here
- If no AllocationCallbackswere provided whenframebufferwas created,pAllocatormust beNULL
Valid Usage (Implicit)
- devicemust be a valid- Devicehandle
- If framebufferis notNULL_HANDLE,framebuffermust be a validFramebufferhandle
- If pAllocatoris notNULL,pAllocatormust be a valid pointer to a validAllocationCallbacksstructure
- If framebufferis a valid handle, it must have been created, allocated, or retrieved fromdevice
Host Synchronization
- Host access to framebuffermust be externally synchronized
See Also
Arguments
| :: forall a io. (Extendss RenderPassCreateInfo a, PokeChain a, MonadIO io) | |
| => Device | 
 | 
| -> RenderPassCreateInfo a | 
 | 
| -> ("allocator" ::: Maybe AllocationCallbacks) | 
 | 
| -> io RenderPass | 
vkCreateRenderPass - Create a new render pass object
Valid Usage (Implicit)
- devicemust be a valid- Devicehandle
- pCreateInfomust be a valid pointer to a valid- RenderPassCreateInfostructure
- If pAllocatoris notNULL,pAllocatormust be a valid pointer to a validAllocationCallbacksstructure
- pRenderPassmust be a valid pointer to a- RenderPasshandle
Return Codes
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.
Arguments
| :: forall io. MonadIO io | |
| => Device | 
 | 
| -> RenderPass | 
 | 
| -> ("allocator" ::: Maybe AllocationCallbacks) | 
 | 
| -> io () | 
vkDestroyRenderPass - Destroy a render pass object
Valid Usage
- All submitted commands that refer to renderPassmust have completed execution
- If AllocationCallbackswere provided whenrenderPasswas created, a compatible set of callbacks must be provided here
- If no AllocationCallbackswere provided whenrenderPasswas created,pAllocatormust beNULL
Valid Usage (Implicit)
- devicemust be a valid- Devicehandle
- If renderPassis notNULL_HANDLE,renderPassmust be a validRenderPasshandle
- If pAllocatoris notNULL,pAllocatormust be a valid pointer to a validAllocationCallbacksstructure
- If renderPassis a valid handle, it must have been created, allocated, or retrieved fromdevice
Host Synchronization
- Host access to renderPassmust be externally synchronized
See Also
getRenderAreaGranularity Source #
Arguments
| :: forall io. MonadIO io | |
| => Device | 
 | 
| -> RenderPass | 
 | 
| -> io ("granularity" ::: Extent2D) | 
vkGetRenderAreaGranularity - Returns the granularity for optimal render area
Description
The conditions leading to an optimal renderArea are:
- the offset.xmember inrenderAreais a multiple of thewidthmember of the returnedExtent2D(the horizontal granularity).
- the offset.ymember inrenderAreais a multiple of theheightof the returnedExtent2D(the vertical granularity).
- either the offset.widthmember inrenderAreais a multiple of the horizontal granularity oroffset.x+offset.widthis equal to thewidthof theframebufferin theRenderPassBeginInfo.
- either the offset.heightmember inrenderAreais a multiple of the vertical granularity oroffset.y+offset.heightis equal to theheightof theframebufferin theRenderPassBeginInfo.
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)
- devicemust be a valid- Devicehandle
- renderPassmust be a valid- RenderPasshandle
- pGranularitymust be a valid pointer to a- Extent2Dstructure
- renderPassmust have been created, allocated, or retrieved from- device
See Also
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
- finalLayoutmust not be- IMAGE_LAYOUT_UNDEFINEDor- IMAGE_LAYOUT_PREINITIALIZED
- If formatis a color format,initialLayoutmust not beIMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL,IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL,IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL, orIMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL
- If formatis a depth/stencil format,initialLayoutmust not beIMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL
- If formatis a color format,finalLayoutmust not beIMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL,IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL,IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL, orIMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL
- If formatis a depth/stencil format,finalLayoutmust not beIMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL
- If the
     separateDepthStencilLayouts
     feature is not enabled, initialLayoutmust not beIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL,IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL,IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL, orIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
- If the
     separateDepthStencilLayouts
     feature is not enabled, finalLayoutmust not beIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL,IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL,IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL, orIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
- If formatis a color format,initialLayoutmust not beIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL,IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL,IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL, orIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
- If formatis a color format,finalLayoutmust not beIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL,IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL,IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL, orIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
- If formatis a depth/stencil format which includes both depth and stencil aspects,initialLayoutmust not beIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL,IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL,IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL, orIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
- If formatis a depth/stencil format which includes both depth and stencil aspects,finalLayoutmust not beIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL,IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL,IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL, orIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
- If formatis a depth/stencil format which includes only the depth aspect,initialLayoutmust not beIMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMALorIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
- If formatis a depth/stencil format which includes only the depth aspect,finalLayoutmust not beIMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMALorIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL
- If formatis a depth/stencil format which includes only the stencil aspect,initialLayoutmust not beIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMALorIMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL
- If formatis a depth/stencil format which includes only the stencil aspect,finalLayoutmust not beIMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMALorIMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL
Valid Usage (Implicit)
- flagsmust be a valid combination of- AttachmentDescriptionFlagBitsvalues
- formatmust be a valid- Formatvalue
- samplesmust be a valid- SampleCountFlagBitsvalue
- loadOpmust be a valid- AttachmentLoadOpvalue
- storeOpmust be a valid- AttachmentStoreOpvalue
- stencilLoadOpmust be a valid- AttachmentLoadOpvalue
- stencilStoreOpmust be a valid- AttachmentStoreOpvalue
- initialLayoutmust be a valid- ImageLayoutvalue
- finalLayoutmust be a valid- ImageLayoutvalue
See Also
AttachmentDescriptionFlags,
 AttachmentLoadOp,
 AttachmentStoreOp,
 Format,
 ImageLayout, RenderPassCreateInfo,
 SampleCountFlagBits
Constructors
| AttachmentDescription | |
| Fields 
 | |
Instances
data AttachmentReference Source #
VkAttachmentReference - Structure specifying an attachment reference
Valid Usage
- If attachmentis notATTACHMENT_UNUSED,layoutmust not beIMAGE_LAYOUT_UNDEFINED,IMAGE_LAYOUT_PREINITIALIZED,IMAGE_LAYOUT_PRESENT_SRC_KHR,IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL_KHR,IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL_KHR,IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL_KHR, orIMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL_KHR
Valid Usage (Implicit)
- layoutmust be a valid- ImageLayoutvalue
See Also
ImageLayout,
 RenderPassFragmentDensityMapCreateInfoEXT,
 SubpassDescription
Constructors
| AttachmentReference | |
| Fields 
 | |
Instances
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:
- SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOMis set.
- The attachment is used as a color or depth/stencil in the subpass.
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
- pipelineBindPointmust be- PIPELINE_BIND_POINT_GRAPHICS
- colorAttachmentCountmust be less than or equal to- PhysicalDeviceLimits::- maxColorAttachments
- If the first use of an attachment in this render pass is as an input
     attachment, and the attachment is not also used as a color or
     depth/stencil attachment in the same subpass, then loadOpmust not beATTACHMENT_LOAD_OP_CLEAR
- If pResolveAttachmentsis notNULL, for each resolve attachment that is notATTACHMENT_UNUSED, the corresponding color attachment must not beATTACHMENT_UNUSED
- If pResolveAttachmentsis notNULL, for each resolve attachment that is notATTACHMENT_UNUSED, the corresponding color attachment must not have a sample count ofSAMPLE_COUNT_1_BIT
- If pResolveAttachmentsis notNULL, each resolve attachment that is notATTACHMENT_UNUSEDmust have a sample count ofSAMPLE_COUNT_1_BIT
- If pResolveAttachmentsis notNULL, each resolve attachment that is notATTACHMENT_UNUSEDmust have the sameFormatas its corresponding color attachment
- All attachments in pColorAttachmentsthat are notATTACHMENT_UNUSEDmust have the same sample count
- All attachments in pInputAttachmentsthat are notATTACHMENT_UNUSEDmust have image formats whose potential format features contain at leastFORMAT_FEATURE_COLOR_ATTACHMENT_BITorFORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT
- All attachments in pColorAttachmentsthat are notATTACHMENT_UNUSEDmust have image formats whose potential format features containFORMAT_FEATURE_COLOR_ATTACHMENT_BIT
- All attachments in pResolveAttachmentsthat are notATTACHMENT_UNUSEDmust have image formats whose potential format features containFORMAT_FEATURE_COLOR_ATTACHMENT_BIT
- If pDepthStencilAttachmentis notNULLand the attachment is notATTACHMENT_UNUSEDthen it must have a image format whose potential format features containFORMAT_FEATURE_DEPTH_STENCIL_ATTACHMENT_BIT
- If the VK_AMD_mixed_attachment_samplesextension is enabled, and all attachments inpColorAttachmentsthat are notATTACHMENT_UNUSEDmust have a sample count that is smaller than or equal to the sample count ofpDepthStencilAttachmentif it is notATTACHMENT_UNUSED
- If neither the VK_AMD_mixed_attachment_samplesnor theVK_NV_framebuffer_mixed_samplesextensions are enabled, and ifpDepthStencilAttachmentis notATTACHMENT_UNUSEDand any attachments inpColorAttachmentsare notATTACHMENT_UNUSED, they must have the same sample count
- The attachmentmember of each element ofpPreserveAttachmentsmust not beATTACHMENT_UNUSED
- Each element of pPreserveAttachmentsmust not also be an element of any other member of the subpass description
- If any attachment is used by more than one AttachmentReferencemember, then each use must use the samelayout
- Each attachment must follow the image layout requirements specified for its attachment type
- If flagsincludesSUBPASS_DESCRIPTION_PER_VIEW_POSITION_X_ONLY_BIT_NVX, it must also includeSUBPASS_DESCRIPTION_PER_VIEW_ATTRIBUTES_BIT_NVX
- If flagsincludesSUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM, and ifpResolveAttachmentsis notNULL, then each resolve attachment must beATTACHMENT_UNUSED
- If flagsincludesSUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM, and ifpDepthStencilResolveAttachmentKHRis notNULL, then the depth/stencil resolve attachment must beATTACHMENT_UNUSED
- If flagsincludesSUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM, then the subpass must be the last subpass in a subpass dependency chain
- If flagsincludesSUBPASS_DESCRIPTION_FRAGMENT_REGION_BIT_QCOM, then the sample count of the input attachments must equalrasterizationSamples
- If flagsincludesSUBPASS_DESCRIPTION_FRAGMENT_REGION_BIT_QCOM, and ifsampleShadingEnableis enabled (explicitly or implicitly) thenminSampleShadingmust equal 0.0
- If the render pass is created with
     RENDER_PASS_CREATE_TRANSFORM_BIT_QCOMeach of the elements ofpInputAttachmentsmust beATTACHMENT_UNUSED
- pDepthStencilAttachmentand- pColorAttachmentsmust not contain references to the same attachment
Valid Usage (Implicit)
- flagsmust be a valid combination of- SubpassDescriptionFlagBitsvalues
- pipelineBindPointmust be a valid- PipelineBindPointvalue
- If inputAttachmentCountis not0,pInputAttachmentsmust be a valid pointer to an array ofinputAttachmentCountvalidAttachmentReferencestructures
- If colorAttachmentCountis not0,pColorAttachmentsmust be a valid pointer to an array ofcolorAttachmentCountvalidAttachmentReferencestructures
- If colorAttachmentCountis not0, andpResolveAttachmentsis notNULL,pResolveAttachmentsmust be a valid pointer to an array ofcolorAttachmentCountvalidAttachmentReferencestructures
- If pDepthStencilAttachmentis notNULL,pDepthStencilAttachmentmust be a valid pointer to a validAttachmentReferencestructure
- If preserveAttachmentCountis not0,pPreserveAttachmentsmust be a valid pointer to an array ofpreserveAttachmentCountuint32_tvalues
See Also
AttachmentReference,
 PipelineBindPoint,
 RenderPassCreateInfo,
 SubpassDescriptionFlags
Constructors
| SubpassDescription | |
| Fields 
 | |
Instances
| Show SubpassDescription Source # | |
| Defined in Vulkan.Core10.Pass Methods showsPrec :: Int -> SubpassDescription -> ShowS # show :: SubpassDescription -> String # showList :: [SubpassDescription] -> ShowS # | |
| FromCStruct SubpassDescription Source # | |
| Defined in Vulkan.Core10.Pass Methods peekCStruct :: Ptr SubpassDescription -> IO SubpassDescription Source # | |
| ToCStruct SubpassDescription Source # | |
| Defined in Vulkan.Core10.Pass Methods withCStruct :: SubpassDescription -> (Ptr SubpassDescription -> IO b) -> IO b Source # pokeCStruct :: Ptr SubpassDescription -> SubpassDescription -> IO b -> IO b Source # withZeroCStruct :: (Ptr SubpassDescription -> IO b) -> IO b Source # pokeZeroCStruct :: Ptr SubpassDescription -> IO b -> IO b Source # cStructSize :: Int Source # | |
| Zero SubpassDescription Source # | |
| Defined in Vulkan.Core10.Pass Methods | |
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 oldLayoutis the attachment’s layout according to the subpass description forsrcSubpass.
- The equivalent to newLayoutis the attachment’s layout according to the subpass description fordstSubpass.
Valid Usage
- If the
     geometry shaders
     feature is not enabled, srcStageMaskmust not containPIPELINE_STAGE_GEOMETRY_SHADER_BIT
- If the
     geometry shaders
     feature is not enabled, dstStageMaskmust not containPIPELINE_STAGE_GEOMETRY_SHADER_BIT
- If the
     tessellation shaders
     feature is not enabled, srcStageMaskmust not containPIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BITorPIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT
- If the
     tessellation shaders
     feature is not enabled, dstStageMaskmust not containPIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BITorPIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT
- srcSubpassmust be less than or equal to- dstSubpass, unless one of them is- SUBPASS_EXTERNAL, to avoid cyclic dependencies and ensure a valid execution order
- srcSubpassand- dstSubpassmust not both be equal to- SUBPASS_EXTERNAL
- If srcSubpassis equal todstSubpassand not all of the stages insrcStageMaskanddstStageMaskare framebuffer-space stages, the logically latest pipeline stage insrcStageMaskmust be logically earlier than or equal to the logically earliest pipeline stage indstStageMask
- Any access flag included in srcAccessMaskmust be supported by one of the pipeline stages insrcStageMask, as specified in the table of supported access types
- Any access flag included in dstAccessMaskmust be supported by one of the pipeline stages indstStageMask, as specified in the table of supported access types
- If srcSubpassequalsdstSubpass, andsrcStageMaskanddstStageMaskboth include a framebuffer-space stage, thendependencyFlagsmust includeDEPENDENCY_BY_REGION_BIT
- If dependencyFlagsincludesDEPENDENCY_VIEW_LOCAL_BIT,srcSubpassmust not be equal toSUBPASS_EXTERNAL
- If dependencyFlagsincludesDEPENDENCY_VIEW_LOCAL_BIT,dstSubpassmust not be equal toSUBPASS_EXTERNAL
- If srcSubpassequalsdstSubpassand that subpass has more than one bit set in the view mask, thendependencyFlagsmust includeDEPENDENCY_VIEW_LOCAL_BIT
- If the
     mesh shaders
     feature is not enabled, srcStageMaskmust not containPIPELINE_STAGE_MESH_SHADER_BIT_NV
- If the
     task shaders
     feature is not enabled, srcStageMaskmust not containPIPELINE_STAGE_TASK_SHADER_BIT_NV
- If the
     mesh shaders
     feature is not enabled, dstStageMaskmust not containPIPELINE_STAGE_MESH_SHADER_BIT_NV
- If the
     task shaders
     feature is not enabled, dstStageMaskmust not containPIPELINE_STAGE_TASK_SHADER_BIT_NV
Valid Usage (Implicit)
- srcStageMaskmust be a valid combination of- PipelineStageFlagBitsvalues
- srcStageMaskmust not be- 0
- dstStageMaskmust be a valid combination of- PipelineStageFlagBitsvalues
- dstStageMaskmust not be- 0
- srcAccessMaskmust be a valid combination of- AccessFlagBitsvalues
- dstAccessMaskmust be a valid combination of- AccessFlagBitsvalues
- dependencyFlagsmust be a valid combination of- DependencyFlagBitsvalues
See Also
AccessFlags,
 DependencyFlags,
 PipelineStageFlags,
 RenderPassCreateInfo
Constructors
| SubpassDependency | |
| Fields 
 | |
Instances
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 attachmentmember of any element ofpInputAttachments,pColorAttachments,pResolveAttachmentsorpDepthStencilAttachment, or any element ofpPreserveAttachmentsin any element ofpSubpassesis notATTACHMENT_UNUSED, it must be less thanattachmentCount
- For any member of pAttachmentswith aloadOpequal toATTACHMENT_LOAD_OP_CLEAR, the first use of that attachment must not specify alayoutequal toIMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMALorIMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL
- For any member of pAttachmentswith astencilLoadOpequal toATTACHMENT_LOAD_OP_CLEAR, the first use of that attachment must not specify alayoutequal toIMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMALorIMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL
- For any member of pAttachmentswith aloadOpequal toATTACHMENT_LOAD_OP_CLEAR, the first use of that attachment must not specify alayoutequal toIMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL
- For any member of pAttachmentswith astencilLoadOpequal toATTACHMENT_LOAD_OP_CLEAR, the first use of that attachment must not specify alayoutequal toIMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL
- If the pNextchain includes aRenderPassInputAttachmentAspectCreateInfostructure, thesubpassmember of each element of itspAspectReferencesmember must be less thansubpassCount
- If the pNextchain includes aRenderPassInputAttachmentAspectCreateInfostructure, theinputAttachmentIndexmember of each element of itspAspectReferencesmember must be less than the value ofinputAttachmentCountin the member ofpSubpassesidentified by itssubpassmember
- If the pNextchain includes aRenderPassInputAttachmentAspectCreateInfostructure, for any element of thepInputAttachmentsmember of any element ofpSubpasseswhere theattachmentmember is notATTACHMENT_UNUSED, theaspectMaskmember of the corresponding element ofRenderPassInputAttachmentAspectCreateInfo::pAspectReferencesmust only include aspects that are present in images of the format specified by the element ofpAttachmentsatattachment
- If the pNextchain includes aRenderPassMultiviewCreateInfostructure, and itssubpassCountmember is not zero, that member must be equal to the value ofsubpassCount
- If the pNextchain includes aRenderPassMultiviewCreateInfostructure, if itsdependencyCountmember is not zero, it must be equal todependencyCount
- If the pNextchain includes aRenderPassMultiviewCreateInfostructure, for each non-zero element ofpViewOffsets, thesrcSubpassanddstSubpassmembers ofpDependenciesat the same index must not be equal
- If the pNextchain includes aRenderPassMultiviewCreateInfostructure, for any element ofpDependencieswith adependencyFlagsmember that does not includeDEPENDENCY_VIEW_LOCAL_BIT, the corresponding element of thepViewOffsetsmember of thatRenderPassMultiviewCreateInfoinstance must be0
- If the pNextchain includes aRenderPassMultiviewCreateInfostructure, elements of itspViewMasksmember must either all be0, or all not be0
- If the pNextchain includes aRenderPassMultiviewCreateInfostructure, and each element of itspViewMasksmember is0, thedependencyFlagsmember of each element ofpDependenciesmust not includeDEPENDENCY_VIEW_LOCAL_BIT
- If the pNextchain includes aRenderPassMultiviewCreateInfostructure, and each element of itspViewMasksmember is0,correlatedViewMaskCountmust be0
- If the pNextchain includes aRenderPassMultiviewCreateInfostructure, each element of itspViewMaskmember must not have a bit set at an index greater than or equal toPhysicalDeviceLimits::maxFramebufferLayers
- For any element of pDependencies, if thesrcSubpassis notSUBPASS_EXTERNAL, all stage flags included in thesrcStageMaskmember of that dependency must be a pipeline stage supported by the pipeline identified by thepipelineBindPointmember of the source subpass
- For any element of pDependencies, if thedstSubpassis notSUBPASS_EXTERNAL, all stage flags included in thedstStageMaskmember of that dependency must be a pipeline stage supported by the pipeline identified by thepipelineBindPointmember of the destination subpass
- The srcSubpassmember of each element ofpDependenciesmust be less thansubpassCount
- The dstSubpassmember of each element ofpDependenciesmust be less thansubpassCount
Valid Usage (Implicit)
- sTypemust be- STRUCTURE_TYPE_RENDER_PASS_CREATE_INFO
- Each pNextmember of any structure (including this one) in thepNextchain must be eitherNULLor a pointer to a valid instance ofRenderPassFragmentDensityMapCreateInfoEXT,RenderPassInputAttachmentAspectCreateInfo, orRenderPassMultiviewCreateInfo
- The sTypevalue of each struct in thepNextchain must be unique
- flagsmust be a valid combination of- RenderPassCreateFlagBitsvalues
- If attachmentCountis not0,pAttachmentsmust be a valid pointer to an array ofattachmentCountvalidAttachmentDescriptionstructures
- pSubpassesmust be a valid pointer to an array of- subpassCountvalid- SubpassDescriptionstructures
- If dependencyCountis not0,pDependenciesmust be a valid pointer to an array ofdependencyCountvalidSubpassDependencystructures
- subpassCountmust be greater than- 0
See Also
AttachmentDescription,
 RenderPassCreateFlags,
 StructureType, SubpassDependency,
 SubpassDescription, createRenderPass
Constructors
| RenderPassCreateInfo | |
| Fields 
 | |
Instances
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
- attachmentCountmust be equal to the attachment count specified in- renderPass
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, andattachmentCountis not0,pAttachmentsmust be a valid pointer to an array ofattachmentCountvalidImageViewhandles
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, each element ofpAttachmentsthat is used as a color attachment or resolve attachment byrenderPassmust have been created with ausagevalue includingIMAGE_USAGE_COLOR_ATTACHMENT_BIT
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, each element ofpAttachmentsthat is used as a depth/stencil attachment byrenderPassmust have been created with ausagevalue includingIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, each element ofpAttachmentsthat is used as a depth/stencil resolve attachment byrenderPassmust have been created with ausagevalue includingIMAGE_USAGE_DEPTH_STENCIL_ATTACHMENT_BIT
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, each element ofpAttachmentsthat is used as an input attachment byrenderPassmust have been created with ausagevalue includingIMAGE_USAGE_INPUT_ATTACHMENT_BIT
- Each element of pAttachmentsthat is used as a fragment density map attachment byrenderPassmust not have been created with aflagsvalue includingIMAGE_CREATE_SUBSAMPLED_BIT_EXT
- If renderPasshas a fragment density map attachment and non-subsample image feature is not enabled, each element ofpAttachmentsmust have been created with aflagsvalue includingIMAGE_CREATE_SUBSAMPLED_BIT_EXTunless that element is the fragment density map attachment
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, each element ofpAttachmentsmust have been created with aFormatvalue that matches theFormatspecified by the correspondingAttachmentDescriptioninrenderPass
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, each element ofpAttachmentsmust have been created with asamplesvalue that matches thesamplesvalue specified by the correspondingAttachmentDescriptioninrenderPass
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, each element ofpAttachmentsthat is used as an input, color, resolve, or depth/stencil attachment byrenderPassmust have been created with a VkImageCreateInfo::widthgreater than or equal towidth
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, each element ofpAttachmentsthat is used as an input, color, resolve, or depth/stencil attachment byrenderPassmust have been created with a VkImageCreateInfo::heightgreater than or equal toheight
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, each element ofpAttachmentsthat is used as an input, color, resolve, or depth/stencil attachment byrenderPassmust have been created with a VkImageViewCreateInfo::subresourceRange.pname:layerCount greater than or equal tolayers
- If renderPasswas specified with non-zero view masks, each element ofpAttachmentsthat is used as an input, color, resolve, or depth/stencil attachment byrenderPassmust have alayerCountgreater than the index of the most significant bit set in any of those view masks
- If renderPasswas specified with non-zero view masks, each element ofpAttachmentsthat is referenced byfragmentDensityMapAttachmentmust have alayerCountequal to1or greater than the index of the most significant bit set in any of those view masks
- If renderPasswas not specified with non-zero view masks, each element ofpAttachmentsthat is referenced byfragmentDensityMapAttachmentmust have alayerCountequal to1
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, an element ofpAttachmentsthat is referenced byfragmentDensityMapAttachmentmust have a width at least as large as \(\left\lceil{\frac{width}{maxFragmentDensityTexelSize_{width}}}\right\rceil\)
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, an element ofpAttachmentsthat is referenced byfragmentDensityMapAttachmentmust have a height at least as large as \(\left\lceil{\frac{height}{maxFragmentDensityTexelSize_{height}}}\right\rceil\)
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, andrenderPasswas specified with non-zero view masks, each element ofpAttachmentsthat is used as a fragment shading rate attachment byrenderPassmust have alayerCountthat is either1, or greater than the index of the most significant bit set in any of those view masks
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, andrenderPasswas not specified with non-zero view masks, each element ofpAttachmentsthat is used as a fragment shading rate attachment byrenderPassmust have alayerCountthat is either1, or greater thanlayers
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, an element ofpAttachmentsthat is used as a fragment shading rate attachment must have a width at least as large as ⌈width\texelWidth⌉, wheretexelWidthis the largest value ofshadingRateAttachmentTexelSize.widthin aFragmentShadingRateAttachmentInfoKHRwhich references that attachment
- If flagsdoes not includeFRAMEBUFFER_CREATE_IMAGELESS_BIT, an element ofpAttachmentsthat is used as a fragment shading rate attachment must have a height at least as large as ⌈height--texelHeight⌉, wheretexelHeightis the largest value of
Constructors
| FramebufferCreateInfo | |
| Fields 
 | |
Instances
newtype Framebuffer Source #
VkFramebuffer - Opaque handle to a framebuffer object
See Also
CommandBufferInheritanceInfo,
 RenderPassBeginInfo,
 createFramebuffer,
 destroyFramebuffer
Constructors
| Framebuffer Word64 | 
Instances
newtype RenderPass Source #
VkRenderPass - Opaque handle to a render pass object
See Also
CommandBufferInheritanceInfo,
 FramebufferCreateInfo,
 GraphicsPipelineCreateInfo,
 RenderPassBeginInfo,
 createRenderPass,
 createRenderPass2,
 createRenderPass2KHR,
 destroyRenderPass,
 getRenderAreaGranularity
Constructors
| RenderPass Word64 | 
Instances
newtype AttachmentLoadOp Source #
VkAttachmentLoadOp - Specify how contents of an attachment are treated at the beginning of a subpass
See Also
Constructors
| AttachmentLoadOp Int32 | 
Bundled Patterns
| pattern ATTACHMENT_LOAD_OP_LOAD :: AttachmentLoadOp | 
 | 
| pattern ATTACHMENT_LOAD_OP_CLEAR :: AttachmentLoadOp | 
 | 
| pattern ATTACHMENT_LOAD_OP_DONT_CARE :: AttachmentLoadOp | 
 | 
Instances
newtype AttachmentStoreOp Source #
VkAttachmentStoreOp - Specify how contents of an attachment are treated at the end of a subpass
Description
Note
ATTACHMENT_STORE_OP_DONT_CARE can cause contents generated during
 previous render passes to be discarded before reaching memory, even if
 no write to the attachment occurs during the current render pass.
See Also
Constructors
| AttachmentStoreOp Int32 | 
Bundled Patterns
| pattern ATTACHMENT_STORE_OP_STORE :: AttachmentStoreOp | 
 | 
| pattern ATTACHMENT_STORE_OP_DONT_CARE :: AttachmentStoreOp | 
 | 
| pattern ATTACHMENT_STORE_OP_NONE_QCOM :: AttachmentStoreOp | 
 | 
Instances
newtype PipelineBindPoint Source #
VkPipelineBindPoint - Specify the bind point of a pipeline object to a command buffer
See Also
DescriptorUpdateTemplateCreateInfo,
 GeneratedCommandsInfoNV,
 GeneratedCommandsMemoryRequirementsInfoNV,
 IndirectCommandsLayoutCreateInfoNV,
 SubpassDescription,
 SubpassDescription2,
 cmdBindDescriptorSets,
 cmdBindPipeline,
 cmdBindPipelineShaderGroupNV,
 cmdPushDescriptorSetKHR
Constructors
| PipelineBindPoint Int32 | 
Bundled Patterns
| pattern PIPELINE_BIND_POINT_GRAPHICS :: PipelineBindPoint | 
 | 
| pattern PIPELINE_BIND_POINT_COMPUTE :: PipelineBindPoint | 
 | 
| pattern PIPELINE_BIND_POINT_RAY_TRACING_KHR :: PipelineBindPoint | 
 | 
Instances
newtype RenderPassCreateFlagBits Source #
VkRenderPassCreateFlagBits - Bitmask specifying additional properties of a renderpass
See Also
Constructors
| RenderPassCreateFlagBits Flags | 
Bundled Patterns
| pattern RENDER_PASS_CREATE_TRANSFORM_BIT_QCOM :: RenderPassCreateFlagBits | 
 | 
Instances
newtype AccessFlagBits Source #
VkAccessFlagBits - Bitmask specifying memory access types that will participate in a memory dependency
Description
Certain access types are only performed by a subset of pipeline stages. Any synchronization command that takes both stage masks and access masks uses both to define the access scopes - only the specified access types performed by the specified stages are included in the access scope. An application must not specify an access flag in a synchronization command if it does not include a pipeline stage in the corresponding stage mask that is able to perform accesses of that type. The following table lists, for each access flag, which pipeline stages can perform that type of access.
Supported access types
See Also
Constructors
| AccessFlagBits Flags | 
Bundled Patterns
Instances
type AccessFlags = AccessFlagBits Source #
newtype AttachmentDescriptionFlagBits Source #
VkAttachmentDescriptionFlagBits - Bitmask specifying additional properties of an attachment
See Also
Constructors
| AttachmentDescriptionFlagBits Flags | 
Bundled Patterns
| pattern ATTACHMENT_DESCRIPTION_MAY_ALIAS_BIT :: AttachmentDescriptionFlagBits | 
 | 
Instances
newtype DependencyFlagBits Source #
VkDependencyFlagBits - Bitmask specifying how execution and memory dependencies are formed
See Also
Constructors
| DependencyFlagBits Flags | 
Bundled Patterns
| pattern DEPENDENCY_BY_REGION_BIT :: DependencyFlagBits | 
 | 
| pattern DEPENDENCY_VIEW_LOCAL_BIT :: DependencyFlagBits | 
 | 
| pattern DEPENDENCY_DEVICE_GROUP_BIT :: DependencyFlagBits | 
 | 
Instances
type DependencyFlags = DependencyFlagBits Source #
newtype SubpassDescriptionFlagBits Source #
VkSubpassDescriptionFlagBits - Bitmask specifying usage of a subpass
Description
Note
Shader resolve operations allow for custom resolve operations, but overdrawing pixels may have a performance and/or power cost. Furthermore, since the content of any depth stencil attachment or color attachment is undefined at the begining of a shader resolve subpass, any depth testing, stencil testing, or blending operation which sources these undefined values also has undefined result value.
See Also
Constructors
| SubpassDescriptionFlagBits Flags | 
Bundled Patterns
| pattern SUBPASS_DESCRIPTION_SHADER_RESOLVE_BIT_QCOM :: SubpassDescriptionFlagBits | 
 | 
| pattern SUBPASS_DESCRIPTION_FRAGMENT_REGION_BIT_QCOM :: SubpassDescriptionFlagBits | 
 | 
| pattern SUBPASS_DESCRIPTION_PER_VIEW_POSITION_X_ONLY_BIT_NVX :: SubpassDescriptionFlagBits | 
 | 
| pattern SUBPASS_DESCRIPTION_PER_VIEW_ATTRIBUTES_BIT_NVX :: SubpassDescriptionFlagBits | 
 | 
Instances
newtype FramebufferCreateFlagBits Source #
VkFramebufferCreateFlagBits - Bitmask specifying framebuffer properties
See Also
Constructors
| FramebufferCreateFlagBits Flags | 
Bundled Patterns
| pattern FRAMEBUFFER_CREATE_IMAGELESS_BIT :: FramebufferCreateFlagBits | 
 |