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

Vulkan.Extensions.VK_KHR_swapchain

Synopsis

Documentation

createSwapchainKHR Source #

Arguments

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

device is the device to create the swapchain for.

-> SwapchainCreateInfoKHR a

pCreateInfo is a pointer to a SwapchainCreateInfoKHR structure specifying the parameters of the created swapchain.

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

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

-> io SwapchainKHR 

vkCreateSwapchainKHR - Create a swapchain

Description

If the oldSwapchain parameter of pCreateInfo is a valid swapchain, which has exclusive full-screen access, that access is released from oldSwapchain. If the command succeeds in this case, the newly created swapchain will automatically acquire exclusive full-screen access from oldSwapchain.

Note

This implicit transfer is intended to avoid exiting and entering full-screen exclusive mode, which may otherwise cause unwanted visual updates to the display.

In some cases, swapchain creation may fail if exclusive full-screen mode is requested for application control, but for some implementation-specific reason exclusive full-screen access is unavailable for the particular combination of parameters provided. If this occurs, ERROR_INITIALIZATION_FAILED will be returned.

Note

In particular, it will fail if the imageExtent member of pCreateInfo does not match the extents of the monitor. Other reasons for failure may include the app not being set as high-dpi aware, or if the physical device and monitor are not compatible in this mode.

Valid Usage (Implicit)

  • device must be a valid Device handle

Host Synchronization

  • Host access to pCreateInfo->surface must be externally synchronized
  • Host access to pCreateInfo->oldSwapchain must be externally synchronized

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, SwapchainCreateInfoKHR, SwapchainKHR

withSwapchainKHR :: forall a io r. (Extendss SwapchainCreateInfoKHR a, PokeChain a, MonadIO io) => Device -> SwapchainCreateInfoKHR a -> Maybe AllocationCallbacks -> (io SwapchainKHR -> (SwapchainKHR -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createSwapchainKHR and destroySwapchainKHR

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

destroySwapchainKHR Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the Device associated with swapchain.

-> SwapchainKHR

swapchain is the swapchain to destroy.

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

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

-> io () 

vkDestroySwapchainKHR - Destroy a swapchain object

Description

The application must not destroy a swapchain until after completion of all outstanding operations on images that were acquired from the swapchain. swapchain and all associated Image handles are destroyed, and must not be acquired or used any more by the application. The memory of each Image will only be freed after that image is no longer used by the presentation engine. For example, if one image of the swapchain is being displayed in a window, the memory for that image may not be freed until the window is destroyed, or another swapchain is created for the window. Destroying the swapchain does not invalidate the parent SurfaceKHR, and a new swapchain can be created with it.

When a swapchain associated with a display surface is destroyed, if the image most recently presented to the display surface is from the swapchain being destroyed, then either any display resources modified by presenting images from any swapchain associated with the display surface must be reverted by the implementation to their state prior to the first present performed on one of these swapchains, or such resources must be left in their current state.

If swapchain has exclusive full-screen access, it is released before the swapchain is destroyed.

Valid Usage

  • All uses of presentable images acquired from swapchain must have completed execution
  • If AllocationCallbacks were provided when swapchain was created, a compatible set of callbacks must be provided here
  • If no AllocationCallbacks were provided when swapchain was created, pAllocator must be NULL

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If swapchain is not NULL_HANDLE, swapchain must be a valid SwapchainKHR handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • Both of device, and swapchain that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Instance

Host Synchronization

  • Host access to swapchain must be externally synchronized

See Also

AllocationCallbacks, Device, SwapchainKHR

getSwapchainImagesKHR Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device associated with swapchain.

-> SwapchainKHR

swapchain is the swapchain to query.

-> io (Result, "swapchainImages" ::: Vector Image) 

vkGetSwapchainImagesKHR - Obtain the array of presentable images associated with a swapchain

Description

If pSwapchainImages is NULL, then the number of presentable images for swapchain is returned in pSwapchainImageCount. Otherwise, pSwapchainImageCount must point to a variable set by the user to the number of elements in the pSwapchainImages array, and on return the variable is overwritten with the number of structures actually written to pSwapchainImages. If the value of pSwapchainImageCount is less than the number of presentable images for swapchain, at most pSwapchainImageCount structures will be written. If pSwapchainImageCount is smaller than the number of presentable images for swapchain, INCOMPLETE will be returned instead of SUCCESS to indicate that not all the available values were returned.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • swapchain must be a valid SwapchainKHR handle
  • pSwapchainImageCount must be a valid pointer to a uint32_t value
  • If the value referenced by pSwapchainImageCount is not 0, and pSwapchainImages is not NULL, pSwapchainImages must be a valid pointer to an array of pSwapchainImageCount Image handles
  • Both of device, and swapchain must have been created, allocated, or retrieved from the same Instance

Return Codes

Success
Failure

See Also

Device, Image, SwapchainKHR

acquireNextImageKHR Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device associated with swapchain.

-> SwapchainKHR

swapchain is the non-retired swapchain from which an image is being acquired.

-> ("timeout" ::: Word64)

timeout specifies how long the function waits, in nanoseconds, if no image is available.

-> Semaphore

semaphore is NULL_HANDLE or a semaphore to signal.

-> Fence

fence is NULL_HANDLE or a fence to signal.

-> io (Result, "imageIndex" ::: Word32) 

vkAcquireNextImageKHR - Retrieve the index of the next available presentable image

Valid Usage

  • swapchain must not be in the retired state
  • If semaphore is not NULL_HANDLE it must be unsignaled
  • If semaphore is not NULL_HANDLE it must not have any uncompleted signal or wait operations pending
  • If fence is not NULL_HANDLE it must be unsignaled and must not be associated with any other queue command that has not yet completed execution on that queue
  • semaphore and fence must not both be equal to NULL_HANDLE
  • If the number of currently acquired images is greater than the difference between the number of images in swapchain and the value of SurfaceCapabilitiesKHR::minImageCount as returned by a call to getPhysicalDeviceSurfaceCapabilities2KHR with the surface used to create swapchain, timeout must not be UINT64_MAX
  • semaphore must have a SemaphoreType of SEMAPHORE_TYPE_BINARY

Valid Usage (Implicit)

  • device must be a valid Device handle
  • swapchain must be a valid SwapchainKHR handle
  • If semaphore is not NULL_HANDLE, semaphore must be a valid Semaphore handle
  • If fence is not NULL_HANDLE, fence must be a valid Fence handle
  • pImageIndex must be a valid pointer to a uint32_t value
  • If semaphore is a valid handle, it must have been created, allocated, or retrieved from device
  • If fence is a valid handle, it must have been created, allocated, or retrieved from device
  • Both of device, and swapchain that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Instance

Host Synchronization

  • Host access to swapchain must be externally synchronized
  • Host access to semaphore must be externally synchronized
  • Host access to fence must be externally synchronized

Return Codes

Success
Failure

See Also

Device, Fence, Semaphore, SwapchainKHR

acquireNextImageKHRSafe Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device associated with swapchain.

-> SwapchainKHR

swapchain is the non-retired swapchain from which an image is being acquired.

-> ("timeout" ::: Word64)

timeout specifies how long the function waits, in nanoseconds, if no image is available.

-> Semaphore

semaphore is NULL_HANDLE or a semaphore to signal.

-> Fence

fence is NULL_HANDLE or a fence to signal.

-> io (Result, "imageIndex" ::: Word32) 

A variant of acquireNextImageKHR which makes a *safe* FFI call

queuePresentKHR Source #

Arguments

:: forall a io. (Extendss PresentInfoKHR a, PokeChain a, MonadIO io) 
=> Queue

queue is a queue that is capable of presentation to the target surface’s platform on the same device as the image’s swapchain.

-> PresentInfoKHR a

pPresentInfo is a pointer to a PresentInfoKHR structure specifying parameters of the presentation.

-> io Result 

vkQueuePresentKHR - Queue an image for presentation

Description

Note

There is no requirement for an application to present images in the same order that they were acquired - applications can arbitrarily present any image that is currently acquired.

Valid Usage

  • Each element of pSwapchains member of pPresentInfo must be a swapchain that is created for a surface for which presentation is supported from queue as determined using a call to getPhysicalDeviceSurfaceSupportKHR
  • If more than one member of pSwapchains was created from a display surface, all display surfaces referenced that refer to the same display must use the same display mode
  • When a semaphore wait operation referring to a binary semaphore defined by the elements of the pWaitSemaphores member of pPresentInfo executes on queue, there must be no other queues waiting on the same semaphore
  • All elements of the pWaitSemaphores member of pPresentInfo must be semaphores that are signaled, or have semaphore signal operations previously submitted for execution
  • All elements of the pWaitSemaphores member of pPresentInfo must be created with a SemaphoreType of SEMAPHORE_TYPE_BINARY
  • All elements of the pWaitSemaphores member of pPresentInfo must reference a semaphore signal operation that has been submitted for execution and any semaphore signal operations on which it depends (if any) must have also been submitted for execution

Any writes to memory backing the images referenced by the pImageIndices and pSwapchains members of pPresentInfo, that are available before queuePresentKHR is executed, are automatically made visible to the read access performed by the presentation engine. This automatic visibility operation for an image happens-after the semaphore signal operation, and happens-before the presentation engine accesses the image.

Queueing an image for presentation defines a set of queue operations, including waiting on the semaphores and submitting a presentation request to the presentation engine. However, the scope of this set of queue operations does not include the actual processing of the image by the presentation engine.

Note

The origin of the native orientation of the surface coordinate system is not specified in the Vulkan specification; it depends on the platform. For most platforms the origin is by default upper-left, meaning the pixel of the presented Image at coordinates (0,0) would appear at the upper left pixel of the platform surface (assuming SURFACE_TRANSFORM_IDENTITY_BIT_KHR, and the display standing the right way up).

If queuePresentKHR fails to enqueue the corresponding set of queue operations, it may return ERROR_OUT_OF_HOST_MEMORY or ERROR_OUT_OF_DEVICE_MEMORY. If it does, the implementation must ensure that the state and contents of any resources or synchronization primitives referenced is unaffected by the call or its failure.

If queuePresentKHR fails in such a way that the implementation is unable to make that guarantee, the implementation must return ERROR_DEVICE_LOST.

However, if the presentation request is rejected by the presentation engine with an error ERROR_OUT_OF_DATE_KHR, ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT, or ERROR_SURFACE_LOST_KHR, the set of queue operations are still considered to be enqueued and thus any semaphore wait operation specified in PresentInfoKHR will execute when the corresponding queue operation is complete.

If any swapchain member of pPresentInfo was created with FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT, ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT will be returned if that swapchain does not have exclusive full-screen access, possibly for implementation-specific reasons outside of the application’s control.

Valid Usage (Implicit)

  • queue must be a valid Queue handle
  • pPresentInfo must be a valid pointer to a valid PresentInfoKHR structure

Host Synchronization

  • Host access to queue must be externally synchronized
  • Host access to pPresentInfo->pWaitSemaphores[] must be externally synchronized
  • Host access to pPresentInfo->pSwapchains[] must be externally synchronized

Command Properties

'

Command Buffer Levels Render Pass Scope Supported Queue Types Pipeline Type
- - Any -

Return Codes

Success
Failure

See Also

PresentInfoKHR, Queue

getDeviceGroupPresentCapabilitiesKHR Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device.

device must be a valid Device handle

-> io DeviceGroupPresentCapabilitiesKHR 

vkGetDeviceGroupPresentCapabilitiesKHR - Query present capabilities from other physical devices

Return Codes

Success
Failure

See Also

Device, DeviceGroupPresentCapabilitiesKHR

getDeviceGroupSurfacePresentModesKHR Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device.

-> SurfaceKHR

surface is the surface.

-> io ("modes" ::: DeviceGroupPresentModeFlagsKHR) 

vkGetDeviceGroupSurfacePresentModesKHR - Query present capabilities for a surface

Description

The modes returned by this command are not invariant, and may change in response to the surface being moved, resized, or occluded. These modes must be a subset of the modes returned by getDeviceGroupPresentCapabilitiesKHR.

Valid Usage (Implicit)

  • device must be a valid Device handle

Host Synchronization

  • Host access to surface must be externally synchronized

Return Codes

Success
Failure

See Also

Device, DeviceGroupPresentModeFlagsKHR, SurfaceKHR

acquireNextImage2KHR Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device associated with swapchain.

-> ("acquireInfo" ::: AcquireNextImageInfoKHR)

pAcquireInfo is a pointer to a AcquireNextImageInfoKHR structure containing parameters of the acquire.

-> io (Result, "imageIndex" ::: Word32) 

vkAcquireNextImage2KHR - Retrieve the index of the next available presentable image

Valid Usage

  • If the number of currently acquired images is greater than the difference between the number of images in the swapchain member of pAcquireInfo and the value of SurfaceCapabilitiesKHR::minImageCount as returned by a call to getPhysicalDeviceSurfaceCapabilities2KHR with the surface used to create swapchain, the timeout member of pAcquireInfo must not be UINT64_MAX

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pAcquireInfo must be a valid pointer to a valid AcquireNextImageInfoKHR structure
  • pImageIndex must be a valid pointer to a uint32_t value

Return Codes

Success
Failure

See Also

AcquireNextImageInfoKHR, Device

acquireNextImage2KHRSafe Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device associated with swapchain.

-> ("acquireInfo" ::: AcquireNextImageInfoKHR)

pAcquireInfo is a pointer to a AcquireNextImageInfoKHR structure containing parameters of the acquire.

-> io (Result, "imageIndex" ::: Word32) 

A variant of acquireNextImage2KHR which makes a *safe* FFI call

getPhysicalDevicePresentRectanglesKHR Source #

Arguments

:: forall io. MonadIO io 
=> PhysicalDevice

physicalDevice is the physical device.

-> SurfaceKHR

surface is the surface.

-> io (Result, "rects" ::: Vector Rect2D) 

vkGetPhysicalDevicePresentRectanglesKHR - Query present rectangles for a surface on a physical device

Description

If pRects is NULL, then the number of rectangles used when presenting the given surface is returned in pRectCount. Otherwise, pRectCount must point to a variable set by the user to the number of elements in the pRects array, and on return the variable is overwritten with the number of structures actually written to pRects. If the value of pRectCount is less than the number of rectangles, at most pRectCount structures will be written. If pRectCount is smaller than the number of rectangles used for the given surface, INCOMPLETE will be returned instead of SUCCESS to indicate that not all the available values were returned.

The values returned by this command are not invariant, and may change in response to the surface being moved, resized, or occluded.

The rectangles returned by this command must not overlap.

Valid Usage (Implicit)

  • surface must be a valid SurfaceKHR handle
  • pRectCount must be a valid pointer to a uint32_t value
  • If the value referenced by pRectCount is not 0, and pRects is not NULL, pRects must be a valid pointer to an array of pRectCount Rect2D structures
  • Both of physicalDevice, and surface must have been created, allocated, or retrieved from the same Instance

Host Synchronization

  • Host access to surface must be externally synchronized

Return Codes

Success
Failure

See Also

PhysicalDevice, Rect2D, SurfaceKHR

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

(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

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

VkPresentInfoKHR - Structure describing parameters of a queue presentation

Description

Before an application can present an image, the image’s layout must be transitioned to the IMAGE_LAYOUT_PRESENT_SRC_KHR layout, or for a shared presentable image the IMAGE_LAYOUT_SHARED_PRESENT_KHR layout.

Note

When transitioning the image to IMAGE_LAYOUT_SHARED_PRESENT_KHR or IMAGE_LAYOUT_PRESENT_SRC_KHR, there is no need to delay subsequent processing, or perform any visibility operations (as queuePresentKHR performs automatic visibility operations). To achieve this, the dstAccessMask member of the ImageMemoryBarrier should be set to 0, and the dstStageMask parameter should be set to PIPELINE_STAGE_BOTTOM_OF_PIPE_BIT.

Valid Usage

  • Each element of pImageIndices must be the index of a presentable image acquired from the swapchain specified by the corresponding element of the pSwapchains array, and the presented image subresource must be in the IMAGE_LAYOUT_PRESENT_SRC_KHR or IMAGE_LAYOUT_SHARED_PRESENT_KHR layout at the time the operation is executed on a Device

Valid Usage (Implicit)

  • Each pNext member of any structure (including this one) in the pNext chain must be either NULL or a pointer to a valid instance of DeviceGroupPresentInfoKHR, DisplayPresentInfoKHR, PresentFrameTokenGGP, PresentRegionsKHR, or PresentTimesInfoGOOGLE
  • The sType value of each struct in the pNext chain must be unique
  • If waitSemaphoreCount is not 0, pWaitSemaphores must be a valid pointer to an array of waitSemaphoreCount valid Semaphore handles
  • pSwapchains must be a valid pointer to an array of swapchainCount valid SwapchainKHR handles
  • pImageIndices must be a valid pointer to an array of swapchainCount uint32_t values
  • If pResults is not NULL, pResults must be a valid pointer to an array of swapchainCount Result values
  • swapchainCount must be greater than 0
  • Both of the elements of pSwapchains, and the elements of pWaitSemaphores that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Instance

See Also

Result, Semaphore, StructureType, SwapchainKHR, queuePresentKHR

Constructors

PresentInfoKHR 

Fields

  • next :: Chain es

    pNext is NULL or a pointer to a structure extending this structure.

  • waitSemaphores :: Vector Semaphore

    pWaitSemaphores is NULL or a pointer to an array of Semaphore objects with waitSemaphoreCount entries, and specifies the semaphores to wait for before issuing the present request.

  • swapchains :: Vector SwapchainKHR

    pSwapchains is a pointer to an array of SwapchainKHR objects with swapchainCount entries. A given swapchain must not appear in this list more than once.

  • imageIndices :: Vector Word32

    pImageIndices is a pointer to an array of indices into the array of each swapchain’s presentable images, with swapchainCount entries. Each entry in this array identifies the image to present on the corresponding entry in the pSwapchains array.

  • results :: Ptr Result

    pResults is a pointer to an array of Result typed elements with swapchainCount entries. Applications that do not need per-swapchain results can use NULL for pResults. If non-NULL, each entry in pResults will be set to the Result for presenting the swapchain corresponding to the same index in pSwapchains.

Instances

Instances details
Extensible PresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Extensions.VK_KHR_swapchain

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

Defined in Vulkan.Extensions.VK_KHR_swapchain

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

Defined in Vulkan.Extensions.VK_KHR_swapchain

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

Defined in Vulkan.Extensions.VK_KHR_swapchain

data DeviceGroupPresentCapabilitiesKHR Source #

VkDeviceGroupPresentCapabilitiesKHR - Present capabilities from other physical devices

Description

modes always has DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR set.

The present mode flags are also used when presenting an image, in DeviceGroupPresentInfoKHR::mode.

If a device group only includes a single physical device, then modes must equal DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR.

Valid Usage (Implicit)

See Also

DeviceGroupPresentModeFlagsKHR, StructureType, getDeviceGroupPresentCapabilitiesKHR

Constructors

DeviceGroupPresentCapabilitiesKHR 

Fields

Instances

Instances details
Show DeviceGroupPresentCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Storable DeviceGroupPresentCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

FromCStruct DeviceGroupPresentCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

ToCStruct DeviceGroupPresentCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Zero DeviceGroupPresentCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

data ImageSwapchainCreateInfoKHR Source #

VkImageSwapchainCreateInfoKHR - Specify that an image will be bound to swapchain memory

Valid Usage

Valid Usage (Implicit)

See Also

StructureType, SwapchainKHR

Constructors

ImageSwapchainCreateInfoKHR 

Fields

Instances

Instances details
Eq ImageSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Show ImageSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Storable ImageSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

FromCStruct ImageSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

ToCStruct ImageSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Zero ImageSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

data BindImageMemorySwapchainInfoKHR Source #

VkBindImageMemorySwapchainInfoKHR - Structure specifying swapchain image memory to bind to

Description

If swapchain is not NULL, the swapchain and imageIndex are used to determine the memory that the image is bound to, instead of memory and memoryOffset.

Memory can be bound to a swapchain and use the pDeviceIndices or pSplitInstanceBindRegions members of BindImageMemoryDeviceGroupInfo.

Valid Usage

  • imageIndex must be less than the number of images in swapchain

Valid Usage (Implicit)

Host Synchronization

  • Host access to swapchain must be externally synchronized

See Also

StructureType, SwapchainKHR

Constructors

BindImageMemorySwapchainInfoKHR 

Fields

Instances

Instances details
Eq BindImageMemorySwapchainInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Show BindImageMemorySwapchainInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Storable BindImageMemorySwapchainInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

FromCStruct BindImageMemorySwapchainInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

ToCStruct BindImageMemorySwapchainInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Zero BindImageMemorySwapchainInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

data AcquireNextImageInfoKHR Source #

VkAcquireNextImageInfoKHR - Structure specifying parameters of the acquire

Description

If acquireNextImageKHR is used, the device mask is considered to include all physical devices in the logical device.

Note

acquireNextImage2KHR signals at most one semaphore, even if the application requests waiting for multiple physical devices to be ready via the deviceMask. However, only a single physical device can wait on that semaphore, since the semaphore becomes unsignaled when the wait succeeds. For other physical devices to wait for the image to be ready, it is necessary for the application to submit semaphore signal operation(s) to that first physical device to signal additional semaphore(s) after the wait succeeds, which the other physical device(s) can wait upon.

Valid Usage

  • swapchain must not be in the retired state
  • If semaphore is not NULL_HANDLE it must be unsignaled
  • If semaphore is not NULL_HANDLE it must not have any uncompleted signal or wait operations pending
  • If fence is not NULL_HANDLE it must be unsignaled and must not be associated with any other queue command that has not yet completed execution on that queue
  • semaphore and fence must not both be equal to NULL_HANDLE
  • deviceMask must be a valid device mask
  • deviceMask must not be zero
  • semaphore must have a SemaphoreType of SEMAPHORE_TYPE_BINARY

Valid Usage (Implicit)

  • pNext must be NULL
  • swapchain must be a valid SwapchainKHR handle
  • If semaphore is not NULL_HANDLE, semaphore must be a valid Semaphore handle
  • If fence is not NULL_HANDLE, fence must be a valid Fence handle
  • Each of fence, semaphore, and swapchain that are valid handles of non-ignored parameters must have been created, allocated, or retrieved from the same Instance

Host Synchronization

  • Host access to swapchain must be externally synchronized
  • Host access to semaphore must be externally synchronized
  • Host access to fence must be externally synchronized

See Also

Fence, Semaphore, StructureType, SwapchainKHR, acquireNextImage2KHR

Constructors

AcquireNextImageInfoKHR 

Fields

Instances

Instances details
Eq AcquireNextImageInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Show AcquireNextImageInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Storable AcquireNextImageInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

FromCStruct AcquireNextImageInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

ToCStruct AcquireNextImageInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Zero AcquireNextImageInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

data DeviceGroupPresentInfoKHR Source #

VkDeviceGroupPresentInfoKHR - Mode and mask controlling which physical devices' images are presented

Description

If mode is DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR, then each element of pDeviceMasks selects which instance of the swapchain image is presented. Each element of pDeviceMasks must have exactly one bit set, and the corresponding physical device must have a presentation engine as reported by DeviceGroupPresentCapabilitiesKHR.

If mode is DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR, then each element of pDeviceMasks selects which instance of the swapchain image is presented. Each element of pDeviceMasks must have exactly one bit set, and some physical device in the logical device must include that bit in its DeviceGroupPresentCapabilitiesKHR::presentMask.

If mode is DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR, then each element of pDeviceMasks selects which instances of the swapchain image are component-wise summed and the sum of those images is presented. If the sum in any component is outside the representable range, the value of that component is undefined. Each element of pDeviceMasks must have a value for which all set bits are set in one of the elements of DeviceGroupPresentCapabilitiesKHR::presentMask.

If mode is DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR, then each element of pDeviceMasks selects which instance(s) of the swapchain images are presented. For each bit set in each element of pDeviceMasks, the corresponding physical device must have a presentation engine as reported by DeviceGroupPresentCapabilitiesKHR.

If DeviceGroupPresentInfoKHR is not provided or swapchainCount is zero then the masks are considered to be 1. If DeviceGroupPresentInfoKHR is not provided, mode is considered to be DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR.

Valid Usage

Valid Usage (Implicit)

  • If swapchainCount is not 0, pDeviceMasks must be a valid pointer to an array of swapchainCount uint32_t values
  • mode must be a valid DeviceGroupPresentModeFlagBitsKHR value

See Also

DeviceGroupPresentModeFlagBitsKHR, StructureType

Constructors

DeviceGroupPresentInfoKHR 

Fields

data DeviceGroupSwapchainCreateInfoKHR Source #

VkDeviceGroupSwapchainCreateInfoKHR - Structure specifying parameters of a newly created swapchain object

Description

If this structure is not present, modes is considered to be DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR.

Valid Usage (Implicit)

See Also

DeviceGroupPresentModeFlagsKHR, StructureType

Constructors

DeviceGroupSwapchainCreateInfoKHR 

Fields

Instances

Instances details
Eq DeviceGroupSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Show DeviceGroupSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Storable DeviceGroupSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

FromCStruct DeviceGroupSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

ToCStruct DeviceGroupSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Zero DeviceGroupSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

newtype DeviceGroupPresentModeFlagBitsKHR Source #

VkDeviceGroupPresentModeFlagBitsKHR - Bitmask specifying supported device group present modes

See Also

DeviceGroupPresentInfoKHR, DeviceGroupPresentModeFlagsKHR

Bundled Patterns

pattern DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR :: DeviceGroupPresentModeFlagBitsKHR

DEVICE_GROUP_PRESENT_MODE_LOCAL_BIT_KHR specifies that any physical device with a presentation engine can present its own swapchain images.

pattern DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR :: DeviceGroupPresentModeFlagBitsKHR

DEVICE_GROUP_PRESENT_MODE_REMOTE_BIT_KHR specifies that any physical device with a presentation engine can present swapchain images from any physical device in its presentMask.

pattern DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR :: DeviceGroupPresentModeFlagBitsKHR

DEVICE_GROUP_PRESENT_MODE_SUM_BIT_KHR specifies that any physical device with a presentation engine can present the sum of swapchain images from any physical devices in its presentMask.

pattern DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR :: DeviceGroupPresentModeFlagBitsKHR

DEVICE_GROUP_PRESENT_MODE_LOCAL_MULTI_DEVICE_BIT_KHR specifies that multiple physical devices with a presentation engine can each present their own swapchain images.

Instances

Instances details
Eq DeviceGroupPresentModeFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Ord DeviceGroupPresentModeFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Read DeviceGroupPresentModeFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Show DeviceGroupPresentModeFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Storable DeviceGroupPresentModeFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Bits DeviceGroupPresentModeFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Methods

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

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

xor :: DeviceGroupPresentModeFlagBitsKHR -> DeviceGroupPresentModeFlagBitsKHR -> DeviceGroupPresentModeFlagBitsKHR #

complement :: DeviceGroupPresentModeFlagBitsKHR -> DeviceGroupPresentModeFlagBitsKHR #

shift :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

rotate :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

zeroBits :: DeviceGroupPresentModeFlagBitsKHR #

bit :: Int -> DeviceGroupPresentModeFlagBitsKHR #

setBit :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

clearBit :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

complementBit :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

testBit :: DeviceGroupPresentModeFlagBitsKHR -> Int -> Bool #

bitSizeMaybe :: DeviceGroupPresentModeFlagBitsKHR -> Maybe Int #

bitSize :: DeviceGroupPresentModeFlagBitsKHR -> Int #

isSigned :: DeviceGroupPresentModeFlagBitsKHR -> Bool #

shiftL :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

unsafeShiftL :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

shiftR :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

unsafeShiftR :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

rotateL :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

rotateR :: DeviceGroupPresentModeFlagBitsKHR -> Int -> DeviceGroupPresentModeFlagBitsKHR #

popCount :: DeviceGroupPresentModeFlagBitsKHR -> Int #

Zero DeviceGroupPresentModeFlagBitsKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

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

pattern KHR_SWAPCHAIN_SPEC_VERSION :: forall a. Integral a => a Source #

type KHR_SWAPCHAIN_EXTENSION_NAME = "VK_KHR_swapchain" Source #

pattern KHR_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

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