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

Vulkan.Core10.Image

Synopsis

Documentation

createImage Source #

Arguments

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

device is the logical device that creates the image.

-> ImageCreateInfo a

pCreateInfo is a pointer to a ImageCreateInfo structure containing parameters to be used to create the image.

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

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

-> io Image 

vkCreateImage - Create a new image object

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pCreateInfo must be a valid pointer to a valid ImageCreateInfo structure
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • pImage must be a valid pointer to a Image handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, Image, ImageCreateInfo

withImage :: forall a io r. (Extendss ImageCreateInfo a, PokeChain a, MonadIO io) => Device -> ImageCreateInfo a -> Maybe AllocationCallbacks -> (io Image -> (Image -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createImage and destroyImage

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

destroyImage Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the image.

-> Image

image is the image to destroy.

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

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

-> io () 

vkDestroyImage - Destroy an image object

Valid Usage

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

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to image must be externally synchronized

See Also

AllocationCallbacks, Device, Image

getImageSubresourceLayout Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the image.

-> Image

image is the image whose layout is being queried.

-> ImageSubresource

pSubresource is a pointer to a ImageSubresource structure selecting a specific image for the image subresource.

-> io SubresourceLayout 

vkGetImageSubresourceLayout - Retrieve information about an image subresource

Description

If the image is linear, then the returned layout is valid for host access.

If the image’s tiling is IMAGE_TILING_LINEAR and its format is a multi-planar format, then getImageSubresourceLayout describes one format plane of the image. If the image’s tiling is IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT, then getImageSubresourceLayout describes one memory plane of the image. If the image’s tiling is IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT and the image is non-linear, then the returned layout has an implementation-dependent meaning; the vendor of the image’s DRM format modifier may provide documentation that explains how to interpret the returned layout.

getImageSubresourceLayout is invariant for the lifetime of a single image. However, the subresource layout of images in Android hardware buffer external memory is not known until the image has been bound to memory, so applications must not call getImageSubresourceLayout for such an image before it has been bound.

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle
  • image must be a valid Image handle
  • pSubresource must be a valid pointer to a valid ImageSubresource structure
  • pLayout must be a valid pointer to a SubresourceLayout structure
  • image must have been created, allocated, or retrieved from device

See Also

Device, Image, ImageSubresource, SubresourceLayout

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

VkImageCreateInfo - Structure specifying the parameters of a newly created image object

Description

Images created with tiling equal to IMAGE_TILING_LINEAR have further restrictions on their limits and capabilities compared to images created with tiling equal to IMAGE_TILING_OPTIMAL. Creation of images with tiling IMAGE_TILING_LINEAR may not be supported unless other parameters meet all of the constraints:

Images created with a format from one of those listed in https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-requiring-sampler-ycbcr-conversion have further restrictions on their limits and capabilities compared to images created with other formats. Creation of images with a format requiring Y′CBCR conversion may not be supported unless other parameters meet all of the constraints:

Implementations may support additional limits and capabilities beyond those listed above.

To determine the set of valid usage bits for a given format, call getPhysicalDeviceFormatProperties.

If the size of the resultant image would exceed maxResourceSize, then createImage must fail and return ERROR_OUT_OF_DEVICE_MEMORY. This failure may occur even when all image creation parameters satisfy their valid usage requirements.

Note

For images created without IMAGE_CREATE_EXTENDED_USAGE_BIT a usage bit is valid if it is supported for the format the image is created with.

For images created with IMAGE_CREATE_EXTENDED_USAGE_BIT a usage bit is valid if it is supported for at least one of the formats a ImageView created from the image can have (see Image Views for more detail).

Valid values for some image creation parameters are limited by a numerical upper bound or by inclusion in a bitset. For example, ImageCreateInfo::arrayLayers is limited by imageCreateMaxArrayLayers, defined below; and ImageCreateInfo::samples is limited by imageCreateSampleCounts, also defined below.

Several limiting values are defined below, as well as assisting values from which the limiting values are derived. The limiting values are referenced by the relevant valid usage statements of ImageCreateInfo.

Valid Usage

  • Each of the following values (as described in Image Creation Limits) must not be undefined imageCreateMaxMipLevels, imageCreateMaxArrayLayers, imageCreateMaxExtent, and imageCreateSampleCounts

Valid Usage (Implicit)

</section> = See Also

Extent3D, Format, ImageCreateFlags, ImageLayout, ImageTiling, ImageType, ImageUsageFlags, SampleCountFlagBits, SharingMode, StructureType, createImage

Constructors

ImageCreateInfo 

Fields

Instances

Instances details
Extensible ImageCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Image

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.Image

Generic (ImageCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Image

Associated Types

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

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

Defined in Vulkan.Core10.Image

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

Defined in Vulkan.Core10.Image

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

Defined in Vulkan.Core10.Image

type Rep (ImageCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Image

type Rep (ImageCreateInfo es) = D1 ('MetaData "ImageCreateInfo" "Vulkan.Core10.Image" "vulkan-3.6-inplace" 'False) (C1 ('MetaCons "ImageCreateInfo" 'PrefixI 'True) (((S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageCreateFlags) :*: S1 ('MetaSel ('Just "imageType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageType))) :*: (S1 ('MetaSel ('Just "format") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Format) :*: (S1 ('MetaSel ('Just "extent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Extent3D) :*: S1 ('MetaSel ('Just "mipLevels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)))) :*: ((S1 ('MetaSel ('Just "arrayLayers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "samples") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SampleCountFlagBits) :*: S1 ('MetaSel ('Just "tiling") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageTiling))) :*: ((S1 ('MetaSel ('Just "usage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageUsageFlags) :*: S1 ('MetaSel ('Just "sharingMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SharingMode)) :*: (S1 ('MetaSel ('Just "queueFamilyIndices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector Word32)) :*: S1 ('MetaSel ('Just "initialLayout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageLayout))))))

data SubresourceLayout Source #

VkSubresourceLayout - Structure specifying subresource layout

Description

If the image is linear, then rowPitch, arrayPitch and depthPitch describe the layout of the image subresource in linear memory. For uncompressed formats, rowPitch is the number of bytes between texels with the same x coordinate in adjacent rows (y coordinates differ by one). arrayPitch is the number of bytes between texels with the same x and y coordinate in adjacent array layers of the image (array layer values differ by one). depthPitch is the number of bytes between texels with the same x and y coordinate in adjacent slices of a 3D image (z coordinates differ by one). Expressed as an addressing formula, the starting byte of a texel in the image subresource has address:

// (x,y,z,layer) are in texel coordinates
address(x,y,z,layer) = layer*arrayPitch + z*depthPitch + y*rowPitch + x*elementSize + offset

For compressed formats, the rowPitch is the number of bytes between compressed texel blocks in adjacent rows. arrayPitch is the number of bytes between compressed texel blocks in adjacent array layers. depthPitch is the number of bytes between compressed texel blocks in adjacent slices of a 3D image.

// (x,y,z,layer) are in compressed texel block coordinates
address(x,y,z,layer) = layer*arrayPitch + z*depthPitch + y*rowPitch + x*compressedTexelBlockByteSize + offset;

The value of arrayPitch is undefined for images that were not created as arrays. depthPitch is defined only for 3D images.

If the image has a single-plane color format and its tiling is IMAGE_TILING_LINEAR , then the aspectMask member of ImageSubresource must be IMAGE_ASPECT_COLOR_BIT.

If the image has a depth/stencil format and its tiling is IMAGE_TILING_LINEAR , then aspectMask must be either IMAGE_ASPECT_DEPTH_BIT or IMAGE_ASPECT_STENCIL_BIT. On implementations that store depth and stencil aspects separately, querying each of these image subresource layouts will return a different offset and size representing the region of memory used for that aspect. On implementations that store depth and stencil aspects interleaved, the same offset and size are returned and represent the interleaved memory allocation.

If the image has a multi-planar format and its tiling is IMAGE_TILING_LINEAR , then the aspectMask member of ImageSubresource must be IMAGE_ASPECT_PLANE_0_BIT, IMAGE_ASPECT_PLANE_1_BIT, or (for 3-plane formats only) IMAGE_ASPECT_PLANE_2_BIT. Querying each of these image subresource layouts will return a different offset and size representing the region of memory used for that plane. If the image is disjoint, then the offset is relative to the base address of the plane. If the image is non-disjoint, then the offset is relative to the base address of the image.

If the image’s tiling is IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT, then the aspectMask member of ImageSubresource must be one of VK_IMAGE_ASPECT_MEMORY_PLANE_i_BIT_EXT, where the maximum allowed plane index i is defined by the DrmFormatModifierPropertiesEXT::drmFormatModifierPlaneCount associated with the image’s ImageCreateInfo::format and modifier. The memory range used by the subresource is described by offset and size. If the image is disjoint, then the offset is relative to the base address of the memory plane. If the image is non-disjoint, then the offset is relative to the base address of the image. If the image is non-linear, then rowPitch, arrayPitch, and depthPitch have an implementation-dependent meaning.

See Also

DeviceSize, ImageDrmFormatModifierExplicitCreateInfoEXT, getImageSubresourceLayout

Constructors

SubresourceLayout 

Fields

  • offset :: DeviceSize

    offset is the byte offset from the start of the image or the plane where the image subresource begins.

  • size :: DeviceSize

    size is the size in bytes of the image subresource. size includes any extra memory that is required based on rowPitch.

  • rowPitch :: DeviceSize

    rowPitch describes the number of bytes between each row of texels in an image.

  • arrayPitch :: DeviceSize

    arrayPitch describes the number of bytes between each array layer of an image.

  • depthPitch :: DeviceSize

    depthPitch describes the number of bytes between each slice of 3D image.

Instances

Instances details
Eq SubresourceLayout Source # 
Instance details

Defined in Vulkan.Core10.Image

Show SubresourceLayout Source # 
Instance details

Defined in Vulkan.Core10.Image

Generic SubresourceLayout Source # 
Instance details

Defined in Vulkan.Core10.Image

Associated Types

type Rep SubresourceLayout :: Type -> Type #

Storable SubresourceLayout Source # 
Instance details

Defined in Vulkan.Core10.Image

FromCStruct SubresourceLayout Source # 
Instance details

Defined in Vulkan.Core10.Image

ToCStruct SubresourceLayout Source # 
Instance details

Defined in Vulkan.Core10.Image

Zero SubresourceLayout Source # 
Instance details

Defined in Vulkan.Core10.Image

type Rep SubresourceLayout Source # 
Instance details

Defined in Vulkan.Core10.Image

newtype Image Source #

Constructors

Image Word64 

Instances

Instances details
Eq Image Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Ord Image Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

compare :: Image -> Image -> Ordering #

(<) :: Image -> Image -> Bool #

(<=) :: Image -> Image -> Bool #

(>) :: Image -> Image -> Bool #

(>=) :: Image -> Image -> Bool #

max :: Image -> Image -> Image #

min :: Image -> Image -> Image #

Show Image Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Storable Image Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

sizeOf :: Image -> Int #

alignment :: Image -> Int #

peekElemOff :: Ptr Image -> Int -> IO Image #

pokeElemOff :: Ptr Image -> Int -> Image -> IO () #

peekByteOff :: Ptr b -> Int -> IO Image #

pokeByteOff :: Ptr b -> Int -> Image -> IO () #

peek :: Ptr Image -> IO Image #

poke :: Ptr Image -> Image -> IO () #

Zero Image Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

zero :: Image Source #

HasObjectType Image Source # 
Instance details

Defined in Vulkan.Core10.Handles

IsHandle Image Source # 
Instance details

Defined in Vulkan.Core10.Handles

newtype ImageLayout Source #

VkImageLayout - Layout of image and image subresources

Description

The type(s) of device access supported by each layout are:

The layout of each image subresource is not a state of the image subresource itself, but is rather a property of how the data in memory is organized, and thus for each mechanism of accessing an image in the API the application must specify a parameter or structure member that indicates which image layout the image subresource(s) are considered to be in when the image will be accessed. For transfer commands, this is a parameter to the command (see https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#clears and https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#copies). For use as a framebuffer attachment, this is a member in the substructures of the RenderPassCreateInfo (see Render Pass). For use in a descriptor set, this is a member in the DescriptorImageInfo structure (see https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-updates).

See Also

AttachmentDescription, AttachmentDescription2, AttachmentDescriptionStencilLayout, AttachmentReference, AttachmentReference2, AttachmentReferenceStencilLayout, DescriptorImageInfo, ImageCreateInfo, ImageMemoryBarrier, cmdBindShadingRateImageNV, cmdBlitImage, cmdClearColorImage, cmdClearDepthStencilImage, cmdCopyBufferToImage, cmdCopyImage, cmdCopyImageToBuffer, cmdResolveImage

Constructors

ImageLayout Int32 

Bundled Patterns

pattern IMAGE_LAYOUT_UNDEFINED :: ImageLayout

IMAGE_LAYOUT_UNDEFINED does not support device access. This layout must only be used as the initialLayout member of ImageCreateInfo or AttachmentDescription, or as the oldLayout in an image transition. When transitioning out of this layout, the contents of the memory are not guaranteed to be preserved.

pattern IMAGE_LAYOUT_GENERAL :: ImageLayout

IMAGE_LAYOUT_GENERAL supports all types of device access.

pattern IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_COLOR_ATTACHMENT_OPTIMAL must only be used as a color or resolve attachment in a Framebuffer. This layout is valid only for image subresources of images created with the IMAGE_USAGE_COLOR_ATTACHMENT_BIT usage bit enabled.

pattern IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_DEPTH_STENCIL_ATTACHMENT_OPTIMAL specifies a layout for both the depth and stencil aspects of a depth/stencil format image allowing read and write access as a depth/stencil attachment. It is equivalent to IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL and IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL.

pattern IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_DEPTH_STENCIL_READ_ONLY_OPTIMAL specifies a layout for both the depth and stencil aspects of a depth/stencil format image allowing read only access as a depth/stencil attachment or in shaders. It is equivalent to IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL and IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL.

pattern IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_SHADER_READ_ONLY_OPTIMAL must only be used as a read-only image in a shader (which can be read as a sampled image, combined image/sampler and/or input attachment). This layout is valid only for image subresources of images created with the IMAGE_USAGE_SAMPLED_BIT or IMAGE_USAGE_INPUT_ATTACHMENT_BIT usage bit enabled.

pattern IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_TRANSFER_SRC_OPTIMAL must only be used as a source image of a transfer command (see the definition of https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-transfer). This layout is valid only for image subresources of images created with the IMAGE_USAGE_TRANSFER_SRC_BIT usage bit enabled.

pattern IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_TRANSFER_DST_OPTIMAL must only be used as a destination image of a transfer command. This layout is valid only for image subresources of images created with the IMAGE_USAGE_TRANSFER_DST_BIT usage bit enabled.

pattern IMAGE_LAYOUT_PREINITIALIZED :: ImageLayout

IMAGE_LAYOUT_PREINITIALIZED does not support device access. This layout must only be used as the initialLayout member of ImageCreateInfo or AttachmentDescription, or as the oldLayout in an image transition. When transitioning out of this layout, the contents of the memory are preserved. This layout is intended to be used as the initial layout for an image whose contents are written by the host, and hence the data can be written to memory immediately, without first executing a layout transition. Currently, IMAGE_LAYOUT_PREINITIALIZED is only useful with linear images because there is not a standard layout defined for IMAGE_TILING_OPTIMAL images.

pattern IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT :: ImageLayout

IMAGE_LAYOUT_FRAGMENT_DENSITY_MAP_OPTIMAL_EXT must only be used as a fragment density map attachment in a RenderPass. This layout is valid only for image subresources of images created with the IMAGE_USAGE_FRAGMENT_DENSITY_MAP_BIT_EXT usage bit enabled.

pattern IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV :: ImageLayout

IMAGE_LAYOUT_SHADING_RATE_OPTIMAL_NV must only be used as a read-only shading-rate-image. This layout is valid only for image subresources of images created with the IMAGE_USAGE_SHADING_RATE_IMAGE_BIT_NV usage bit enabled.

pattern IMAGE_LAYOUT_SHARED_PRESENT_KHR :: ImageLayout

IMAGE_LAYOUT_SHARED_PRESENT_KHR is valid only for shared presentable images, and must be used for any usage the image supports.

pattern IMAGE_LAYOUT_PRESENT_SRC_KHR :: ImageLayout

IMAGE_LAYOUT_PRESENT_SRC_KHR must only be used for presenting a presentable image for display. A swapchain’s image must be transitioned to this layout before calling queuePresentKHR, and must be transitioned away from this layout after calling acquireNextImageKHR.

pattern IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL specifies a layout for the stencil aspect of a depth/stencil format image allowing read-only access as a stencil attachment or in shaders.

pattern IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL specifies a layout for the stencil aspect of a depth/stencil format image allowing read and write access as a stencil attachment.

pattern IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL specifies a layout for the depth aspect of a depth/stencil format image allowing read-only access as a depth attachment or in shaders.

pattern IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL specifies a layout for the depth aspect of a depth/stencil format image allowing read and write access as a depth attachment.

pattern IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_DEPTH_ATTACHMENT_STENCIL_READ_ONLY_OPTIMAL specifies a layout for depth/stencil format images allowing read and write access to the depth aspect as a depth attachment, and read only access to the stencil aspect as a stencil attachment or in shaders. It is equivalent to IMAGE_LAYOUT_DEPTH_ATTACHMENT_OPTIMAL and IMAGE_LAYOUT_STENCIL_READ_ONLY_OPTIMAL.

pattern IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL :: ImageLayout

IMAGE_LAYOUT_DEPTH_READ_ONLY_STENCIL_ATTACHMENT_OPTIMAL specifies a layout for depth/stencil format images allowing read and write access to the stencil aspect as a stencil attachment, and read only access to the depth aspect as a depth attachment or in shaders. It is equivalent to IMAGE_LAYOUT_DEPTH_READ_ONLY_OPTIMAL and IMAGE_LAYOUT_STENCIL_ATTACHMENT_OPTIMAL.

Instances

Instances details
Eq ImageLayout Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageLayout

Ord ImageLayout Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageLayout

Read ImageLayout Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageLayout

Show ImageLayout Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageLayout

Storable ImageLayout Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageLayout

Zero ImageLayout Source # 
Instance details

Defined in Vulkan.Core10.Enums.ImageLayout