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

Vulkan.Extensions.VK_KHR_device_group

Synopsis

Documentation

getDeviceGroupPeerMemoryFeaturesKHR :: MonadIO io => Device -> ("heapIndex" ::: Word32) -> ("localDeviceIndex" ::: Word32) -> ("remoteDeviceIndex" ::: Word32) -> io ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) Source #

cmdSetDeviceMaskKHR :: MonadIO io => CommandBuffer -> ("deviceMask" ::: Word32) -> io () Source #

cmdDispatchBaseKHR :: MonadIO io => CommandBuffer -> ("baseGroupX" ::: Word32) -> ("baseGroupY" ::: Word32) -> ("baseGroupZ" ::: Word32) -> ("groupCountX" ::: Word32) -> ("groupCountY" ::: Word32) -> ("groupCountZ" ::: Word32) -> io () Source #

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

type KHR_DEVICE_GROUP_EXTENSION_NAME = "VK_KHR_device_group" Source #

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

newtype SurfaceKHR Source #

Constructors

SurfaceKHR Word64 

Instances

Instances details
Eq SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Storable SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle SurfaceKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

newtype SwapchainKHR Source #

VkSwapchainKHR - Opaque handle to a swapchain object

Description

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

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

Note

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

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

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

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

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

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

Note

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

See Also

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

Constructors

SwapchainKHR Word64 

Instances

Instances details
Eq SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Ord SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Show SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Storable SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

Zero SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

HasObjectType SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

IsHandle SwapchainKHR Source # 
Instance details

Defined in Vulkan.Extensions.Handles

data 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

Generic DeviceGroupPresentCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Associated Types

type Rep DeviceGroupPresentCapabilitiesKHR :: Type -> Type #

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

type Rep DeviceGroupPresentCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

type Rep DeviceGroupPresentCapabilitiesKHR = D1 ('MetaData "DeviceGroupPresentCapabilitiesKHR" "Vulkan.Extensions.VK_KHR_swapchain" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "DeviceGroupPresentCapabilitiesKHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "presentMask") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector Word32)) :*: S1 ('MetaSel ('Just "modes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DeviceGroupPresentModeFlagsKHR)))

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

Generic ImageSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Associated Types

type Rep ImageSwapchainCreateInfoKHR :: Type -> Type #

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

type Rep ImageSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

type Rep ImageSwapchainCreateInfoKHR = D1 ('MetaData "ImageSwapchainCreateInfoKHR" "Vulkan.Extensions.VK_KHR_swapchain" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "ImageSwapchainCreateInfoKHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "swapchain") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SwapchainKHR)))

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

Generic BindImageMemorySwapchainInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Associated Types

type Rep BindImageMemorySwapchainInfoKHR :: Type -> Type #

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

type Rep BindImageMemorySwapchainInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

type Rep BindImageMemorySwapchainInfoKHR = D1 ('MetaData "BindImageMemorySwapchainInfoKHR" "Vulkan.Extensions.VK_KHR_swapchain" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "BindImageMemorySwapchainInfoKHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "swapchain") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SwapchainKHR) :*: S1 ('MetaSel ('Just "imageIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32)))

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

Generic AcquireNextImageInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Associated Types

type Rep AcquireNextImageInfoKHR :: Type -> Type #

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

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

Instances

Instances details
Show DeviceGroupPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Generic DeviceGroupPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Associated Types

type Rep DeviceGroupPresentInfoKHR :: Type -> Type #

FromCStruct DeviceGroupPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

ToCStruct DeviceGroupPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Zero DeviceGroupPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

type Rep DeviceGroupPresentInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

type Rep DeviceGroupPresentInfoKHR = D1 ('MetaData "DeviceGroupPresentInfoKHR" "Vulkan.Extensions.VK_KHR_swapchain" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "DeviceGroupPresentInfoKHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "deviceMasks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Vector Word32)) :*: S1 ('MetaSel ('Just "mode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DeviceGroupPresentModeFlagBitsKHR)))

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

Generic DeviceGroupSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

Associated Types

type Rep DeviceGroupSwapchainCreateInfoKHR :: Type -> Type #

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

type Rep DeviceGroupSwapchainCreateInfoKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_swapchain

type Rep DeviceGroupSwapchainCreateInfoKHR = D1 ('MetaData "DeviceGroupSwapchainCreateInfoKHR" "Vulkan.Extensions.VK_KHR_swapchain" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "DeviceGroupSwapchainCreateInfoKHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "modes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DeviceGroupPresentModeFlagsKHR)))

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

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