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

Vulkan.Extensions.VK_KHR_display_swapchain

Synopsis

Documentation

createSharedSwapchainsKHR Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device to create the swapchains for.

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

pCreateInfos is a pointer to an array of SwapchainCreateInfoKHR structures specifying the parameters of the created swapchains.

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

pAllocator is the allocator used for host memory allocated for the swapchain objects when there is no more specific allocator available (see Memory Allocation).

-> io ("swapchains" ::: Vector SwapchainKHR) 

vkCreateSharedSwapchainsKHR - Create multiple swapchains that share presentable images

Description

createSharedSwapchainsKHR is similar to createSwapchainKHR, except that it takes an array of SwapchainCreateInfoKHR structures, and returns an array of swapchain objects.

The swapchain creation parameters that affect the properties and number of presentable images must match between all the swapchains. If the displays used by any of the swapchains do not use the same presentable image layout or are incompatible in a way that prevents sharing images, swapchain creation will fail with the result code ERROR_INCOMPATIBLE_DISPLAY_KHR. If any error occurs, no swapchains will be created. Images presented to multiple swapchains must be re-acquired from all of them before transitioning away from IMAGE_LAYOUT_PRESENT_SRC_KHR. After destroying one or more of the swapchains, the remaining swapchains and the presentable images can continue to be used.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pCreateInfos must be a valid pointer to an array of swapchainCount valid SwapchainCreateInfoKHR structures
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • pSwapchains must be a valid pointer to an array of swapchainCount SwapchainKHR handles
  • swapchainCount must be greater than 0

Host Synchronization

  • Host access to pCreateInfos[].surface must be externally synchronized
  • Host access to pCreateInfos[].oldSwapchain must be externally synchronized

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, SwapchainCreateInfoKHR, SwapchainKHR

data DisplayPresentInfoKHR Source #

VkDisplayPresentInfoKHR - Structure describing parameters of a queue presentation to a swapchain

Description

If the extent of the srcRect and dstRect are not equal, the presented pixels will be scaled accordingly.

Valid Usage

  • srcRect must specify a rectangular region that is a subset of the image being presented
  • dstRect must specify a rectangular region that is a subset of the visibleRegion parameter of the display mode the swapchain being presented uses
  • If the persistentContent member of the DisplayPropertiesKHR structure returned by getPhysicalDeviceDisplayPropertiesKHR for the display the present operation targets then persistent must be FALSE

Valid Usage (Implicit)

See Also

Bool32, Rect2D, StructureType

Constructors

DisplayPresentInfoKHR 

Fields

  • srcRect :: Rect2D

    srcRect is a rectangular region of pixels to present. It must be a subset of the image being presented. If DisplayPresentInfoKHR is not specified, this region will be assumed to be the entire presentable image.

  • dstRect :: Rect2D

    dstRect is a rectangular region within the visible region of the swapchain’s display mode. If DisplayPresentInfoKHR is not specified, this region will be assumed to be the entire visible region of the visible region of the swapchain’s mode. If the specified rectangle is a subset of the display mode’s visible region, content from display planes below the swapchain’s plane will be visible outside the rectangle. If there are no planes below the swapchain’s, the area outside the specified rectangle will be black. If portions of the specified rectangle are outside of the display’s visible region, pixels mapping only to those portions of the rectangle will be discarded.

  • persistent :: Bool

    persistent: If this is TRUE, the display engine will enable buffered mode on displays that support it. This allows the display engine to stop sending content to the display until a new image is presented. The display will instead maintain a copy of the last presented image. This allows less power to be used, but may increase presentation latency. If DisplayPresentInfoKHR is not specified, persistent mode will not be used.

Instances

Instances details
Show DisplayPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_display_swapchain

Generic DisplayPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_display_swapchain

Associated Types

type Rep DisplayPresentInfoKHR :: Type -> Type #

FromCStruct DisplayPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_display_swapchain

ToCStruct DisplayPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_display_swapchain

Zero DisplayPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_display_swapchain

type Rep DisplayPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_display_swapchain

type Rep DisplayPresentInfoKHR = D1 ('MetaData "DisplayPresentInfoKHR" "Vulkan.Extensions.VK_KHR_display_swapchain" "vulkan-3.5-inplace" 'False) (C1 ('MetaCons "DisplayPresentInfoKHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "srcRect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Rect2D) :*: (S1 ('MetaSel ('Just "dstRect") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Rect2D) :*: S1 ('MetaSel ('Just "persistent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool))))

type KHR_DISPLAY_SWAPCHAIN_EXTENSION_NAME = "VK_KHR_display_swapchain" Source #

pattern KHR_DISPLAY_SWAPCHAIN_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #

newtype SurfaceKHR Source #

Constructors

SurfaceKHR Word64 

Instances

Instances details
Eq SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Storable SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

newtype SwapchainKHR Source #

VkSwapchainKHR - Opaque handle to a swapchain object

Description

A swapchain is an abstraction for an array of presentable images that are associated with a surface. The presentable images are represented by Image objects created by the platform. One image (which can be an array image for multiview/stereoscopic-3D surfaces) is displayed at a time, but multiple images can be queued for presentation. An application renders to the image, and then queues the image for presentation to the surface.

A native window cannot be associated with more than one non-retired swapchain at a time. Further, swapchains cannot be created for native windows that have a non-Vulkan graphics API surface associated with them.

Note

The presentation engine is an abstraction for the platform’s compositor or display engine.

The presentation engine may be synchronous or asynchronous with respect to the application and/or logical device.

Some implementations may use the device’s graphics queue or dedicated presentation hardware to perform presentation.

The presentable images of a swapchain are owned by the presentation engine. An application can acquire use of a presentable image from the presentation engine. Use of a presentable image must occur only after the image is returned by acquireNextImageKHR, and before it is presented by queuePresentKHR. This includes transitioning the image layout and rendering commands.

An application can acquire use of a presentable image with acquireNextImageKHR. After acquiring a presentable image and before modifying it, the application must use a synchronization primitive to ensure that the presentation engine has finished reading from the image. The application can then transition the image’s layout, queue rendering commands to it, etc. Finally, the application presents the image with queuePresentKHR, which releases the acquisition of the image.

The presentation engine controls the order in which presentable images are acquired for use by the application.

Note

This allows the platform to handle situations which require out-of-order return of images after presentation. At the same time, it allows the application to generate command buffers referencing all of the images in the swapchain at initialization time, rather than in its main loop.

See Also

AcquireNextImageInfoKHR, BindImageMemorySwapchainInfoKHR, ImageSwapchainCreateInfoKHR, PresentInfoKHR, SwapchainCreateInfoKHR, acquireFullScreenExclusiveModeEXT, acquireNextImageKHR, createSharedSwapchainsKHR, createSwapchainKHR, destroySwapchainKHR, getPastPresentationTimingGOOGLE, getRefreshCycleDurationGOOGLE, getSwapchainCounterEXT, getSwapchainImagesKHR, getSwapchainStatusKHR, releaseFullScreenExclusiveModeEXT, setHdrMetadataEXT, setLocalDimmingAMD

Constructors

SwapchainKHR Word64 

Instances

Instances details
Eq SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Storable SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

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

VkSwapchainCreateInfoKHR - Structure specifying parameters of a newly created swapchain object

Description

Note

On some platforms, it is normal that maxImageExtent may become (0, 0), for example when the window is minimized. In such a case, it is not possible to create a swapchain due to the Valid Usage requirements.

  • imageArrayLayers is the number of views in a multiview/stereo surface. For non-stereoscopic-3D applications, this value is 1.
  • imageUsage is a bitmask of ImageUsageFlagBits describing the intended usage of the (acquired) swapchain images.
  • imageSharingMode is the sharing mode used for the image(s) of the swapchain.
  • queueFamilyIndexCount is the number of queue families having access to the image(s) of the swapchain when imageSharingMode is SHARING_MODE_CONCURRENT.
  • pQueueFamilyIndices is a pointer to an array of queue family indices having access to the images(s) of the swapchain when imageSharingMode is SHARING_MODE_CONCURRENT.
  • preTransform is a SurfaceTransformFlagBitsKHR value describing the transform, relative to the presentation engine’s natural orientation, applied to the image content prior to presentation. If it does not match the currentTransform value returned by getPhysicalDeviceSurfaceCapabilitiesKHR, the presentation engine will transform the image content as part of the presentation operation.
  • compositeAlpha is a CompositeAlphaFlagBitsKHR value indicating the alpha compositing mode to use when this surface is composited together with other surfaces on certain window systems.
  • presentMode is the presentation mode the swapchain will use. A swapchain’s present mode determines how incoming present requests will be processed and queued internally.
  • clipped specifies whether the Vulkan implementation is allowed to discard rendering operations that affect regions of the surface that are not visible.

    • If set to TRUE, the presentable images associated with the swapchain may not own all of their pixels. Pixels in the presentable images that correspond to regions of the target surface obscured by another window on the desktop, or subject to some other clipping mechanism will have undefined content when read back. Fragment shaders may not execute for these pixels, and thus any side effects they would have had will not occur. TRUE value does not guarantee any clipping will occur, but allows more optimal presentation methods to be used on some platforms.
    • If set to FALSE, presentable images associated with the swapchain will own all of the pixels they contain.

Note

Applications should set this value to TRUE if they do not expect to read back the content of presentable images before presenting them or after reacquiring them, and if their fragment shaders do not have any side effects that require them to run for all pixels in the presentable image.

  • oldSwapchain is NULL_HANDLE, or the existing non-retired swapchain currently associated with surface. Providing a valid oldSwapchain may aid in the resource reuse, and also allows the application to still present any images that are already acquired from it.

Upon calling createSwapchainKHR with an oldSwapchain that is not NULL_HANDLE, oldSwapchain is retired — even if creation of the new swapchain fails. The new swapchain is created in the non-retired state whether or not oldSwapchain is NULL_HANDLE.

Upon calling createSwapchainKHR with an oldSwapchain that is not NULL_HANDLE, any images from oldSwapchain that are not acquired by the application may be freed by the implementation, which may occur even if creation of the new swapchain fails. The application can destroy oldSwapchain to free all memory associated with oldSwapchain.

Note

Multiple retired swapchains can be associated with the same SurfaceKHR through multiple uses of oldSwapchain that outnumber calls to destroySwapchainKHR.

After oldSwapchain is retired, the application can pass to queuePresentKHR any images it had already acquired from oldSwapchain. E.g., an application may present an image from the old swapchain before an image from the new swapchain is ready to be presented. As usual, queuePresentKHR may fail if oldSwapchain has entered a state that causes ERROR_OUT_OF_DATE_KHR to be returned.

The application can continue to use a shared presentable image obtained from oldSwapchain until a presentable image is acquired from the new swapchain, as long as it has not entered a state that causes it to return ERROR_OUT_OF_DATE_KHR.

Valid Usage

Valid Usage (Implicit)

See Also

Bool32, ColorSpaceKHR, CompositeAlphaFlagBitsKHR, Extent2D, Format, ImageUsageFlags, PresentModeKHR, SharingMode, StructureType, SurfaceKHR, SurfaceTransformFlagBitsKHR, SwapchainCreateFlagsKHR, SwapchainKHR, createSharedSwapchainsKHR, createSwapchainKHR

Constructors

SwapchainCreateInfoKHR 

Fields

Instances

Instances details
Extensible SwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Extensions.VK_KHR_swapchain

Generic (SwapchainCreateInfoKHR es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Associated Types

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

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

Defined in Vulkan.Extensions.VK_KHR_swapchain

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

Defined in Vulkan.Extensions.VK_KHR_swapchain

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

Defined in Vulkan.Extensions.VK_KHR_swapchain

type Rep (SwapchainCreateInfoKHR es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

type Rep (SwapchainCreateInfoKHR es) = D1 ('MetaData "SwapchainCreateInfoKHR" "Vulkan.Extensions.VK_KHR_swapchain" "vulkan-3.5-inplace" 'False) (C1 ('MetaCons "SwapchainCreateInfoKHR" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SwapchainCreateFlagsKHR)) :*: (S1 ('MetaSel ('Just "surface") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SurfaceKHR) :*: S1 ('MetaSel ('Just "minImageCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32))) :*: ((S1 ('MetaSel ('Just "imageFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Format) :*: S1 ('MetaSel ('Just "imageColorSpace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ColorSpaceKHR)) :*: (S1 ('MetaSel ('Just "imageExtent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Extent2D) :*: S1 ('MetaSel ('Just "imageArrayLayers") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)))) :*: (((S1 ('MetaSel ('Just "imageUsage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ImageUsageFlags) :*: S1 ('MetaSel ('Just "imageSharingMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SharingMode)) :*: (S1 ('MetaSel ('Just "queueFamilyIndices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector Word32)) :*: S1 ('MetaSel ('Just "preTransform") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SurfaceTransformFlagBitsKHR))) :*: ((S1 ('MetaSel ('Just "compositeAlpha") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CompositeAlphaFlagBitsKHR) :*: S1 ('MetaSel ('Just "presentMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PresentModeKHR)) :*: (S1 ('MetaSel ('Just "clipped") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "oldSwapchain") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SwapchainKHR))))))

newtype PresentModeKHR Source #

VkPresentModeKHR - presentation mode supported for a surface

Description

The supported ImageUsageFlagBits of the presentable images of a swapchain created for a surface may differ depending on the presentation mode, and can be determined as per the table below:

Presentation mode Image usage flags
PRESENT_MODE_IMMEDIATE_KHR SurfaceCapabilitiesKHR::supportedUsageFlags
PRESENT_MODE_MAILBOX_KHR SurfaceCapabilitiesKHR::supportedUsageFlags
PRESENT_MODE_FIFO_KHR SurfaceCapabilitiesKHR::supportedUsageFlags
PRESENT_MODE_FIFO_RELAXED_KHR SurfaceCapabilitiesKHR::supportedUsageFlags
PRESENT_MODE_SHARED_DEMAND_REFRESH_KHR SharedPresentSurfaceCapabilitiesKHR::sharedPresentSupportedUsageFlags
PRESENT_MODE_SHARED_CONTINUOUS_REFRESH_KHR SharedPresentSurfaceCapabilitiesKHR::sharedPresentSupportedUsageFlags

Presentable image usage queries

Note

For reference, the mode indicated by PRESENT_MODE_FIFO_KHR is equivalent to the behavior of {wgl|glX|egl}SwapBuffers with a swap interval of 1, while the mode indicated by PRESENT_MODE_FIFO_RELAXED_KHR is equivalent to the behavior of {wgl|glX}SwapBuffers with a swap interval of -1 (from the {WGL|GLX}_EXT_swap_control_tear extensions).

See Also

SwapchainCreateInfoKHR, getPhysicalDeviceSurfacePresentModes2EXT, getPhysicalDeviceSurfacePresentModesKHR

Constructors

PresentModeKHR Int32 

Bundled Patterns

pattern PRESENT_MODE_IMMEDIATE_KHR :: PresentModeKHR

PRESENT_MODE_IMMEDIATE_KHR specifies that the presentation engine does not wait for a vertical blanking period to update the current image, meaning this mode may result in visible tearing. No internal queuing of presentation requests is needed, as the requests are applied immediately.

pattern PRESENT_MODE_MAILBOX_KHR :: PresentModeKHR

PRESENT_MODE_MAILBOX_KHR specifies that the presentation engine waits for the next vertical blanking period to update the current image. Tearing cannot be observed. An internal single-entry queue is used to hold pending presentation requests. If the queue is full when a new presentation request is received, the new request replaces the existing entry, and any images associated with the prior entry become available for re-use by the application. One request is removed from the queue and processed during each vertical blanking period in which the queue is non-empty.

pattern PRESENT_MODE_FIFO_KHR :: PresentModeKHR

PRESENT_MODE_FIFO_KHR specifies that the presentation engine waits for the next vertical blanking period to update the current image. Tearing cannot be observed. An internal queue is used to hold pending presentation requests. New requests are appended to the end of the queue, and one request is removed from the beginning of the queue and processed during each vertical blanking period in which the queue is non-empty. This is the only value of presentMode that is required to be supported.

pattern PRESENT_MODE_FIFO_RELAXED_KHR :: PresentModeKHR

PRESENT_MODE_FIFO_RELAXED_KHR specifies that the presentation engine generally waits for the next vertical blanking period to update the current image. If a vertical blanking period has already passed since the last update of the current image then the presentation engine does not wait for another vertical blanking period for the update, meaning this mode may result in visible tearing in this case. This mode is useful for reducing visual stutter with an application that will mostly present a new image before the next vertical blanking period, but may occasionally be late, and present a new image just after the next vertical blanking period. An internal queue is used to hold pending presentation requests. New requests are appended to the end of the queue, and one request is removed from the beginning of the queue and processed during or after each vertical blanking period in which the queue is non-empty.

pattern PRESENT_MODE_SHARED_CONTINUOUS_REFRESH_KHR :: PresentModeKHR

PRESENT_MODE_SHARED_CONTINUOUS_REFRESH_KHR specifies that the presentation engine and application have concurrent access to a single image, which is referred to as a shared presentable image. The presentation engine periodically updates the current image on its regular refresh cycle. The application is only required to make one initial presentation request, after which the presentation engine must update the current image without any need for further presentation requests. The application can indicate the image contents have been updated by making a presentation request, but this does not guarantee the timing of when it will be updated. This mode may result in visible tearing if rendering to the image is not timed correctly.

pattern PRESENT_MODE_SHARED_DEMAND_REFRESH_KHR :: PresentModeKHR

PRESENT_MODE_SHARED_DEMAND_REFRESH_KHR specifies that the presentation engine and application have concurrent access to a single image, which is referred to as a shared presentable image. The presentation engine is only required to update the current image after a new presentation request is received. Therefore the application must make a presentation request whenever an update is required. However, the presentation engine may update the current image at any point, meaning this mode may result in visible tearing.

Instances

Instances details
Eq PresentModeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Ord PresentModeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Read PresentModeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Show PresentModeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Storable PresentModeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Zero PresentModeKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

newtype ColorSpaceKHR Source #

VkColorSpaceKHR - supported color space of the presentation engine

Description

Note

In the initial release of the VK_KHR_surface and VK_KHR_swapchain extensions, the token VK_COLORSPACE_SRGB_NONLINEAR_KHR was used. Starting in the 2016-05-13 updates to the extension branches, matching release 1.0.13 of the core API specification, COLOR_SPACE_SRGB_NONLINEAR_KHR is used instead for consistency with Vulkan naming rules. The older enum is still available for backwards compatibility.

Note

In older versions of this extension COLOR_SPACE_DISPLAY_P3_LINEAR_EXT was misnamed COLOR_SPACE_DCI_P3_LINEAR_EXT. This has been updated to indicate that it uses RGB color encoding, not XYZ. The old name is deprecated but is maintained for backwards compatibility.

The color components of non-linear color space swap chain images must have had the appropriate transfer function applied. The color space selected for the swap chain image will not affect the processing of data written into the image by the implementation. Vulkan requires that all implementations support the sRGB transfer function by use of an SRGB pixel format. Other transfer functions, such as SMPTE 170M or SMPTE2084, can be performed by the application shader. This extension defines enums for ColorSpaceKHR that correspond to the following color spaces:

Name Red Primary Green Primary Blue Primary White-point Transfer function
DCI-P3 1.000, 0.000 0.000, 1.000 0.000, 0.000 0.3333, 0.3333 DCI P3
Display-P3 0.680, 0.320 0.265, 0.690 0.150, 0.060 0.3127, 0.3290 (D65) Display-P3
BT709 0.640, 0.330 0.300, 0.600 0.150, 0.060 0.3127, 0.3290 (D65) ITU (SMPTE 170M)
sRGB 0.640, 0.330 0.300, 0.600 0.150, 0.060 0.3127, 0.3290 (D65) sRGB
extended sRGB 0.640, 0.330 0.300, 0.600 0.150, 0.060 0.3127, 0.3290 (D65) extended sRGB
HDR10_ST2084 0.708, 0.292 0.170, 0.797 0.131, 0.046 0.3127, 0.3290 (D65) ST2084 PQ
DOLBYVISION 0.708, 0.292 0.170, 0.797 0.131, 0.046 0.3127, 0.3290 (D65) ST2084 PQ
HDR10_HLG 0.708, 0.292 0.170, 0.797 0.131, 0.046 0.3127, 0.3290 (D65) HLG
AdobeRGB 0.640, 0.330 0.210, 0.710 0.150, 0.060 0.3127, 0.3290 (D65) AdobeRGB

Color Spaces and Attributes

The transfer functions are described in the “Transfer Functions” chapter of the Khronos Data Format Specification.

Except Display-P3 OETF, which is:

[begin{aligned} E & = begin{cases} 1.055 times L^{1 over 2.4} - 0.055 & text{for} 0.0030186 leq L leq 1 -- 12.92 times L & text{for} 0 leq L < 0.0030186

Constructors

ColorSpaceKHR Int32 

Bundled Patterns

pattern COLOR_SPACE_DISPLAY_P3_LINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_DISPLAY_P3_LINEAR_EXT specifies support for the Display-P3 color space to be displayed using a linear EOTF.

pattern COLOR_SPACE_SRGB_NONLINEAR_KHR :: ColorSpaceKHR

COLOR_SPACE_SRGB_NONLINEAR_KHR specifies support for the sRGB color space.

pattern COLOR_SPACE_DISPLAY_NATIVE_AMD :: ColorSpaceKHR

COLOR_SPACE_DISPLAY_NATIVE_AMD specifies support for the display’s native color space. This matches the color space expectations of AMD’s FreeSync2 standard, for displays supporting it.

pattern COLOR_SPACE_EXTENDED_SRGB_NONLINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_EXTENDED_SRGB_NONLINEAR_EXT specifies support for the extended sRGB color space to be displayed using an sRGB EOTF.

pattern COLOR_SPACE_PASS_THROUGH_EXT :: ColorSpaceKHR

COLOR_SPACE_PASS_THROUGH_EXT specifies that color components are used “as is”. This is intended to allow applications to supply data for color spaces not described here.

pattern COLOR_SPACE_ADOBERGB_NONLINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_ADOBERGB_NONLINEAR_EXT specifies support for the AdobeRGB color space to be displayed using the Gamma 2.2 EOTF.

pattern COLOR_SPACE_ADOBERGB_LINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_ADOBERGB_LINEAR_EXT specifies support for the AdobeRGB color space to be displayed using a linear EOTF.

pattern COLOR_SPACE_HDR10_HLG_EXT :: ColorSpaceKHR

COLOR_SPACE_HDR10_HLG_EXT specifies support for the HDR10 (BT2020 color space) to be displayed using the Hybrid Log Gamma (HLG) EOTF.

pattern COLOR_SPACE_DOLBYVISION_EXT :: ColorSpaceKHR

COLOR_SPACE_DOLBYVISION_EXT specifies support for the Dolby Vision (BT2020 color space), proprietary encoding, to be displayed using the SMPTE ST2084 EOTF.

pattern COLOR_SPACE_HDR10_ST2084_EXT :: ColorSpaceKHR

COLOR_SPACE_HDR10_ST2084_EXT specifies support for the HDR10 (BT2020 color) space to be displayed using the SMPTE ST2084 Perceptual Quantizer (PQ) EOTF.

pattern COLOR_SPACE_BT2020_LINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_BT2020_LINEAR_EXT specifies support for the BT2020 color space to be displayed using a linear EOTF.

pattern COLOR_SPACE_BT709_NONLINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_BT709_NONLINEAR_EXT specifies support for the BT709 color space to be displayed using the SMPTE 170M EOTF.

pattern COLOR_SPACE_BT709_LINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_BT709_LINEAR_EXT specifies support for the BT709 color space to be displayed using a linear EOTF.

pattern COLOR_SPACE_DCI_P3_NONLINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_DCI_P3_NONLINEAR_EXT specifies support for the DCI-P3 color space to be displayed using the DCI-P3 EOTF. Note that values in such an image are interpreted as XYZ encoded color data by the presentation engine.

pattern COLOR_SPACE_EXTENDED_SRGB_LINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_EXTENDED_SRGB_LINEAR_EXT specifies support for the extended sRGB color space to be displayed using a linear EOTF.

pattern COLOR_SPACE_DISPLAY_P3_NONLINEAR_EXT :: ColorSpaceKHR

COLOR_SPACE_DISPLAY_P3_NONLINEAR_EXT specifies support for the Display-P3 color space to be displayed using an sRGB-like EOTF (defined below).

Instances

Instances details
Eq ColorSpaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Ord ColorSpaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Read ColorSpaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Show ColorSpaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Storable ColorSpaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Zero ColorSpaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

newtype CompositeAlphaFlagBitsKHR Source #

VkCompositeAlphaFlagBitsKHR - alpha compositing modes supported on a device

Description

These values are described as follows:

See Also

CompositeAlphaFlagsKHR, SwapchainCreateInfoKHR

Bundled Patterns

pattern COMPOSITE_ALPHA_OPAQUE_BIT_KHR :: CompositeAlphaFlagBitsKHR

COMPOSITE_ALPHA_OPAQUE_BIT_KHR: The alpha channel, if it exists, of the images is ignored in the compositing process. Instead, the image is treated as if it has a constant alpha of 1.0.

pattern COMPOSITE_ALPHA_PRE_MULTIPLIED_BIT_KHR :: CompositeAlphaFlagBitsKHR

COMPOSITE_ALPHA_PRE_MULTIPLIED_BIT_KHR: The alpha channel, if it exists, of the images is respected in the compositing process. The non-alpha channels of the image are expected to already be multiplied by the alpha channel by the application.

pattern COMPOSITE_ALPHA_POST_MULTIPLIED_BIT_KHR :: CompositeAlphaFlagBitsKHR

COMPOSITE_ALPHA_POST_MULTIPLIED_BIT_KHR: The alpha channel, if it exists, of the images is respected in the compositing process. The non-alpha channels of the image are not expected to already be multiplied by the alpha channel by the application; instead, the compositor will multiply the non-alpha channels of the image by the alpha channel during compositing.

pattern COMPOSITE_ALPHA_INHERIT_BIT_KHR :: CompositeAlphaFlagBitsKHR

COMPOSITE_ALPHA_INHERIT_BIT_KHR: The way in which the presentation engine treats the alpha channel in the images is unknown to the Vulkan API. Instead, the application is responsible for setting the composite alpha blending mode using native window system commands. If the application does not set the blending mode using native window system commands, then a platform-specific default will be used.

Instances

Instances details
Eq CompositeAlphaFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Ord CompositeAlphaFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Read CompositeAlphaFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Show CompositeAlphaFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Storable CompositeAlphaFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Bits CompositeAlphaFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Methods

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

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

xor :: CompositeAlphaFlagBitsKHR -> CompositeAlphaFlagBitsKHR -> CompositeAlphaFlagBitsKHR #

complement :: CompositeAlphaFlagBitsKHR -> CompositeAlphaFlagBitsKHR #

shift :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

rotate :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

zeroBits :: CompositeAlphaFlagBitsKHR #

bit :: Int -> CompositeAlphaFlagBitsKHR #

setBit :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

clearBit :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

complementBit :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

testBit :: CompositeAlphaFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: CompositeAlphaFlagBitsKHR -> Maybe Int #

bitSize :: CompositeAlphaFlagBitsKHR -> Int #

isSigned :: CompositeAlphaFlagBitsKHR -> Bool #

shiftL :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

unsafeShiftL :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

shiftR :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

unsafeShiftR :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

rotateL :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

rotateR :: CompositeAlphaFlagBitsKHR -> Int -> CompositeAlphaFlagBitsKHR #

popCount :: CompositeAlphaFlagBitsKHR -> Int #

Zero CompositeAlphaFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

newtype SurfaceTransformFlagBitsKHR Source #

Bundled Patterns

pattern SURFACE_TRANSFORM_IDENTITY_BIT_KHR :: SurfaceTransformFlagBitsKHR

SURFACE_TRANSFORM_IDENTITY_BIT_KHR specifies that image content is presented without being transformed.

pattern SURFACE_TRANSFORM_ROTATE_90_BIT_KHR :: SurfaceTransformFlagBitsKHR

SURFACE_TRANSFORM_ROTATE_90_BIT_KHR specifies that image content is rotated 90 degrees clockwise.

pattern SURFACE_TRANSFORM_ROTATE_180_BIT_KHR :: SurfaceTransformFlagBitsKHR

SURFACE_TRANSFORM_ROTATE_180_BIT_KHR specifies that image content is rotated 180 degrees clockwise.

pattern SURFACE_TRANSFORM_ROTATE_270_BIT_KHR :: SurfaceTransformFlagBitsKHR

SURFACE_TRANSFORM_ROTATE_270_BIT_KHR specifies that image content is rotated 270 degrees clockwise.

pattern SURFACE_TRANSFORM_HORIZONTAL_MIRROR_BIT_KHR :: SurfaceTransformFlagBitsKHR

SURFACE_TRANSFORM_HORIZONTAL_MIRROR_BIT_KHR specifies that image content is mirrored horizontally.

pattern SURFACE_TRANSFORM_HORIZONTAL_MIRROR_ROTATE_90_BIT_KHR :: SurfaceTransformFlagBitsKHR

SURFACE_TRANSFORM_HORIZONTAL_MIRROR_ROTATE_90_BIT_KHR specifies that image content is mirrored horizontally, then rotated 90 degrees clockwise.

pattern SURFACE_TRANSFORM_HORIZONTAL_MIRROR_ROTATE_180_BIT_KHR :: SurfaceTransformFlagBitsKHR

SURFACE_TRANSFORM_HORIZONTAL_MIRROR_ROTATE_180_BIT_KHR specifies that image content is mirrored horizontally, then rotated 180 degrees clockwise.

pattern SURFACE_TRANSFORM_HORIZONTAL_MIRROR_ROTATE_270_BIT_KHR :: SurfaceTransformFlagBitsKHR

SURFACE_TRANSFORM_HORIZONTAL_MIRROR_ROTATE_270_BIT_KHR specifies that image content is mirrored horizontally, then rotated 270 degrees clockwise.

pattern SURFACE_TRANSFORM_INHERIT_BIT_KHR :: SurfaceTransformFlagBitsKHR

SURFACE_TRANSFORM_INHERIT_BIT_KHR specifies that the presentation transform is not specified, and is instead determined by platform-specific considerations and mechanisms outside Vulkan.

Instances

Instances details
Eq SurfaceTransformFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Ord SurfaceTransformFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Read SurfaceTransformFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Show SurfaceTransformFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Storable SurfaceTransformFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Bits SurfaceTransformFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Methods

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

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

xor :: SurfaceTransformFlagBitsKHR -> SurfaceTransformFlagBitsKHR -> SurfaceTransformFlagBitsKHR #

complement :: SurfaceTransformFlagBitsKHR -> SurfaceTransformFlagBitsKHR #

shift :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

rotate :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

zeroBits :: SurfaceTransformFlagBitsKHR #

bit :: Int -> SurfaceTransformFlagBitsKHR #

setBit :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

clearBit :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

complementBit :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

testBit :: SurfaceTransformFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: SurfaceTransformFlagBitsKHR -> Maybe Int #

bitSize :: SurfaceTransformFlagBitsKHR -> Int #

isSigned :: SurfaceTransformFlagBitsKHR -> Bool #

shiftL :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

unsafeShiftL :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

shiftR :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

unsafeShiftR :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

rotateL :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

rotateR :: SurfaceTransformFlagBitsKHR -> Int -> SurfaceTransformFlagBitsKHR #

popCount :: SurfaceTransformFlagBitsKHR -> Int #

Zero SurfaceTransformFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

newtype SwapchainCreateFlagBitsKHR Source #

VkSwapchainCreateFlagBitsKHR - Bitmask controlling swapchain creation

See Also

SwapchainCreateFlagsKHR

Bundled Patterns

pattern SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR :: SwapchainCreateFlagBitsKHR

SWAPCHAIN_CREATE_MUTABLE_FORMAT_BIT_KHR specifies that the images of the swapchain can be used to create a ImageView with a different format than what the swapchain was created with. The list of allowed image view formats are specified by adding a ImageFormatListCreateInfo structure to the pNext chain of SwapchainCreateInfoKHR. In addition, this flag also specifies that the swapchain can be created with usage flags that are not supported for the format the swapchain is created with but are supported for at least one of the allowed image view formats.

pattern SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR :: SwapchainCreateFlagBitsKHR

SWAPCHAIN_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT_KHR specifies that images created from the swapchain (i.e. with the swapchain member of ImageSwapchainCreateInfoKHR set to this swapchain’s handle) must use IMAGE_CREATE_SPLIT_INSTANCE_BIND_REGIONS_BIT.

pattern SWAPCHAIN_CREATE_PROTECTED_BIT_KHR :: SwapchainCreateFlagBitsKHR

SWAPCHAIN_CREATE_PROTECTED_BIT_KHR specifies that images created from the swapchain are protected images.

Instances

Instances details
Eq SwapchainCreateFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Ord SwapchainCreateFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Read SwapchainCreateFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Show SwapchainCreateFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Storable SwapchainCreateFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Bits SwapchainCreateFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Methods

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

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

xor :: SwapchainCreateFlagBitsKHR -> SwapchainCreateFlagBitsKHR -> SwapchainCreateFlagBitsKHR #

complement :: SwapchainCreateFlagBitsKHR -> SwapchainCreateFlagBitsKHR #

shift :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

rotate :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

zeroBits :: SwapchainCreateFlagBitsKHR #

bit :: Int -> SwapchainCreateFlagBitsKHR #

setBit :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

clearBit :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

complementBit :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

testBit :: SwapchainCreateFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: SwapchainCreateFlagBitsKHR -> Maybe Int #

bitSize :: SwapchainCreateFlagBitsKHR -> Int #

isSigned :: SwapchainCreateFlagBitsKHR -> Bool #

shiftL :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

unsafeShiftL :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

shiftR :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

unsafeShiftR :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

rotateL :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

rotateR :: SwapchainCreateFlagBitsKHR -> Int -> SwapchainCreateFlagBitsKHR #

popCount :: SwapchainCreateFlagBitsKHR -> Int #

Zero SwapchainCreateFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain