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

Vulkan.Extensions.VK_EXT_full_screen_exclusive

Synopsis

Documentation

getPhysicalDeviceSurfacePresentModes2EXT Source #

Arguments

:: forall a io. (Extendss PhysicalDeviceSurfaceInfo2KHR a, PokeChain a, MonadIO io) 
=> PhysicalDevice

physicalDevice is the physical device that will be associated with the swapchain to be created, as described for createSwapchainKHR.

-> PhysicalDeviceSurfaceInfo2KHR a

pSurfaceInfo is a pointer to a PhysicalDeviceSurfaceInfo2KHR structure describing the surface and other fixed parameters that would be consumed by createSwapchainKHR.

-> io (Result, "presentModes" ::: Vector PresentModeKHR) 

vkGetPhysicalDeviceSurfacePresentModes2EXT - Query supported presentation modes

Description

getPhysicalDeviceSurfacePresentModes2EXT behaves similarly to getPhysicalDeviceSurfacePresentModesKHR, with the ability to specify extended inputs via chained input structures.

Valid Usage (Implicit)

  • pSurfaceInfo must be a valid pointer to a valid PhysicalDeviceSurfaceInfo2KHR structure
  • pPresentModeCount must be a valid pointer to a uint32_t value
  • If the value referenced by pPresentModeCount is not 0, and pPresentModes is not NULL, pPresentModes must be a valid pointer to an array of pPresentModeCount PresentModeKHR values

Return Codes

Success
Failure

See Also

PhysicalDevice, PhysicalDeviceSurfaceInfo2KHR, PresentModeKHR

getDeviceGroupSurfacePresentModes2EXT Source #

Arguments

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

device is the logical device.

device must be a valid Device handle

-> PhysicalDeviceSurfaceInfo2KHR a

pSurfaceInfo is a pointer to a PhysicalDeviceSurfaceInfo2KHR structure describing the surface and other fixed parameters that would be consumed by createSwapchainKHR.

pSurfaceInfo must be a valid pointer to a valid PhysicalDeviceSurfaceInfo2KHR structure

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

vkGetDeviceGroupSurfacePresentModes2EXT - Query device group present capabilities for a surface

Description

getDeviceGroupSurfacePresentModes2EXT behaves similarly to getDeviceGroupSurfacePresentModesKHR, with the ability to specify extended inputs via chained input structures.

Return Codes

Success
Failure

See Also

Device, DeviceGroupPresentModeFlagsKHR, PhysicalDeviceSurfaceInfo2KHR

acquireFullScreenExclusiveModeEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device associated with swapchain.

-> SwapchainKHR

swapchain is the swapchain to acquire exclusive full-screen access for.

-> io () 

vkAcquireFullScreenExclusiveModeEXT - Acquire full-screen exclusive mode for a swapchain

Valid Usage

  • swapchain must not be in the retired state

A return value of SUCCESS indicates that the swapchain successfully acquired exclusive full-screen access. The swapchain will retain this exclusivity until either the application releases exclusive full-screen access with releaseFullScreenExclusiveModeEXT, destroys the swapchain, or if any of the swapchain commands return ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT indicating that the mode was lost because of platform-specific changes.

If the swapchain was unable to acquire exclusive full-screen access to the display then ERROR_INITIALIZATION_FAILED is returned. An application can attempt to acquire exclusive full-screen access again for the same swapchain even if this command fails, or if ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT has been returned by a swapchain command.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • swapchain must be a valid SwapchainKHR handle
  • Both of device, and swapchain must have been created, allocated, or retrieved from the same Instance

Return Codes

Success
Failure

See Also

Device, SwapchainKHR

releaseFullScreenExclusiveModeEXT Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the device associated with swapchain.

-> SwapchainKHR

swapchain is the swapchain to release exclusive full-screen access from.

swapchain must not be in the retired state

swapchain must be a swapchain created with a SurfaceFullScreenExclusiveInfoEXT structure, with fullScreenExclusive set to FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT

-> io () 

vkReleaseFullScreenExclusiveModeEXT - Release full-screen exclusive mode from a swapchain

Description

Note

Applications will not be able to present to swapchain after this call until exclusive full-screen access is reacquired. This is usually useful to handle when an application is minimised or otherwise intends to stop presenting for a time.

Valid Usage

See Also

Device, SwapchainKHR

data SurfaceFullScreenExclusiveInfoEXT Source #

VkSurfaceFullScreenExclusiveInfoEXT - Structure specifying the preferred full-screen transition behavior

Description

If this structure is not present, fullScreenExclusive is considered to be FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT.

Valid Usage (Implicit)

See Also

FullScreenExclusiveEXT, StructureType

Constructors

SurfaceFullScreenExclusiveInfoEXT 

Fields

Instances

Instances details
Eq SurfaceFullScreenExclusiveInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Show SurfaceFullScreenExclusiveInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Generic SurfaceFullScreenExclusiveInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Associated Types

type Rep SurfaceFullScreenExclusiveInfoEXT :: Type -> Type #

Storable SurfaceFullScreenExclusiveInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

FromCStruct SurfaceFullScreenExclusiveInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

ToCStruct SurfaceFullScreenExclusiveInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Zero SurfaceFullScreenExclusiveInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

type Rep SurfaceFullScreenExclusiveInfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

type Rep SurfaceFullScreenExclusiveInfoEXT = D1 ('MetaData "SurfaceFullScreenExclusiveInfoEXT" "Vulkan.Extensions.VK_EXT_full_screen_exclusive" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "SurfaceFullScreenExclusiveInfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "fullScreenExclusive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 FullScreenExclusiveEXT)))

data SurfaceFullScreenExclusiveWin32InfoEXT Source #

VkSurfaceFullScreenExclusiveWin32InfoEXT - Structure specifying additional creation parameters specific to Win32 fullscreen exclusive mode

Description

Note

If hmonitor is invalidated (e.g. the monitor is unplugged) during the lifetime of a swapchain created with this structure, operations on that swapchain will return ERROR_OUT_OF_DATE_KHR.

Note

It is the responsibility of the application to change the display settings of the targeted Win32 display using the appropriate platform APIs. Such changes may alter the surface capabilities reported for the created surface.

Valid Usage (Implicit)

See Also

StructureType

Constructors

SurfaceFullScreenExclusiveWin32InfoEXT 

Fields

Instances

Instances details
Eq SurfaceFullScreenExclusiveWin32InfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Show SurfaceFullScreenExclusiveWin32InfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Generic SurfaceFullScreenExclusiveWin32InfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Storable SurfaceFullScreenExclusiveWin32InfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

FromCStruct SurfaceFullScreenExclusiveWin32InfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

ToCStruct SurfaceFullScreenExclusiveWin32InfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Zero SurfaceFullScreenExclusiveWin32InfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

type Rep SurfaceFullScreenExclusiveWin32InfoEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

type Rep SurfaceFullScreenExclusiveWin32InfoEXT = D1 ('MetaData "SurfaceFullScreenExclusiveWin32InfoEXT" "Vulkan.Extensions.VK_EXT_full_screen_exclusive" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "SurfaceFullScreenExclusiveWin32InfoEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "hmonitor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 HMONITOR)))

data SurfaceCapabilitiesFullScreenExclusiveEXT Source #

VkSurfaceCapabilitiesFullScreenExclusiveEXT - Structure describing full screen exclusive capabilities of a surface

Description

This structure can be included in the pNext chain of SurfaceCapabilities2KHR to determine support for exclusive full-screen access. If fullScreenExclusiveSupported is FALSE, it indicates that exclusive full-screen access is not obtainable for this surface.

Applications must not attempt to create swapchains with FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT set if fullScreenExclusiveSupported is FALSE.

Valid Usage (Implicit)

See Also

Bool32, StructureType

Instances

Instances details
Eq SurfaceCapabilitiesFullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Show SurfaceCapabilitiesFullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Generic SurfaceCapabilitiesFullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Storable SurfaceCapabilitiesFullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

FromCStruct SurfaceCapabilitiesFullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

ToCStruct SurfaceCapabilitiesFullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Zero SurfaceCapabilitiesFullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

type Rep SurfaceCapabilitiesFullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

type Rep SurfaceCapabilitiesFullScreenExclusiveEXT = D1 ('MetaData "SurfaceCapabilitiesFullScreenExclusiveEXT" "Vulkan.Extensions.VK_EXT_full_screen_exclusive" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "SurfaceCapabilitiesFullScreenExclusiveEXT" 'PrefixI 'True) (S1 ('MetaSel ('Just "fullScreenExclusiveSupported") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Bool)))

newtype FullScreenExclusiveEXT Source #

VkFullScreenExclusiveEXT - Hint values an application can specify affecting full-screen transition behavior

See Also

SurfaceFullScreenExclusiveInfoEXT

Bundled Patterns

pattern FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT :: FullScreenExclusiveEXT

FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT indicates the implementation should determine the appropriate full-screen method by whatever means it deems appropriate.

pattern FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT :: FullScreenExclusiveEXT

FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT indicates the implementation may use full-screen exclusive mechanisms when available. Such mechanisms may result in better performance and/or the availability of different presentation capabilities, but may require a more disruptive transition during swapchain initialization, first presentation and/or destruction.

pattern FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT :: FullScreenExclusiveEXT

FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT indicates the implementation should avoid using full-screen mechanisms which rely on disruptive transitions.

pattern FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT :: FullScreenExclusiveEXT

FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT indicates the application will manage full-screen exclusive mode by using the acquireFullScreenExclusiveModeEXT and releaseFullScreenExclusiveModeEXT commands.

Instances

Instances details
Eq FullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Ord FullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Read FullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Show FullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Storable FullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

Zero FullScreenExclusiveEXT Source # 
Instance details

Defined in Vulkan.Extensions.VK_EXT_full_screen_exclusive

type EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME = "VK_EXT_full_screen_exclusive" Source #

type HMONITOR = Ptr () 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 PhysicalDeviceSurfaceInfo2KHR (es :: [Type]) Source #

VkPhysicalDeviceSurfaceInfo2KHR - Structure specifying a surface and related swapchain creation parameters

Description

The members of PhysicalDeviceSurfaceInfo2KHR correspond to the arguments to getPhysicalDeviceSurfaceCapabilitiesKHR, with sType and pNext added for extensibility.

Additional capabilities of a surface may be available to swapchains created with different full-screen exclusive settings - particularly if exclusive full-screen access is application controlled. These additional capabilities can be queried by adding a SurfaceFullScreenExclusiveInfoEXT structure to the pNext chain of this structure when used to query surface properties. Additionally, for Win32 surfaces with application controlled exclusive full-screen access, chaining a SurfaceFullScreenExclusiveWin32InfoEXT structure may also report additional surface capabilities. These additional capabilities only apply to swapchains created with the same parameters included in the pNext chain of SwapchainCreateInfoKHR.

Valid Usage

Valid Usage (Implicit)

See Also

StructureType, SurfaceKHR, getDeviceGroupSurfacePresentModes2EXT, getPhysicalDeviceSurfaceCapabilities2KHR, getPhysicalDeviceSurfaceFormats2KHR, getPhysicalDeviceSurfacePresentModes2EXT

Constructors

PhysicalDeviceSurfaceInfo2KHR 

Fields

  • next :: Chain es

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

  • surface :: SurfaceKHR

    surface is the surface that will be associated with the swapchain.

Instances

Instances details
Extensible PhysicalDeviceSurfaceInfo2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Generic (PhysicalDeviceSurfaceInfo2KHR es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Associated Types

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

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

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

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

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

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

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

type Rep (PhysicalDeviceSurfaceInfo2KHR es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

type Rep (PhysicalDeviceSurfaceInfo2KHR es) = D1 ('MetaData "PhysicalDeviceSurfaceInfo2KHR" "Vulkan.Extensions.VK_KHR_get_surface_capabilities2" "vulkan-3.6.9-inplace" 'False) (C1 ('MetaCons "PhysicalDeviceSurfaceInfo2KHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: S1 ('MetaSel ('Just "surface") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SurfaceKHR)))

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