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

Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Synopsis

Documentation

getPhysicalDeviceSurfaceCapabilities2KHR Source #

Arguments

:: forall a b io. (Extendss PhysicalDeviceSurfaceInfo2KHR a, Extendss SurfaceCapabilities2KHR b, PokeChain a, PokeChain b, PeekChain b, 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 (SurfaceCapabilities2KHR b) 

vkGetPhysicalDeviceSurfaceCapabilities2KHR - Reports capabilities of a surface on a physical device

Description

getPhysicalDeviceSurfaceCapabilities2KHR behaves similarly to getPhysicalDeviceSurfaceCapabilitiesKHR, with the ability to specify extended inputs via chained input structures, and to return extended information via chained output structures.

Valid Usage

Valid Usage (Implicit)

Return Codes

Success
Failure

See Also

PhysicalDevice, PhysicalDeviceSurfaceInfo2KHR, SurfaceCapabilities2KHR

getPhysicalDeviceSurfaceFormats2KHR 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, "surfaceFormats" ::: Vector SurfaceFormat2KHR) 

vkGetPhysicalDeviceSurfaceFormats2KHR - Query color formats supported by surface

Description

getPhysicalDeviceSurfaceFormats2KHR behaves similarly to getPhysicalDeviceSurfaceFormatsKHR, with the ability to be extended via pNext chains.

If pSurfaceFormats is NULL, then the number of format tuples supported for the given surface is returned in pSurfaceFormatCount. Otherwise, pSurfaceFormatCount must point to a variable set by the user to the number of elements in the pSurfaceFormats array, and on return the variable is overwritten with the number of structures actually written to pSurfaceFormats. If the value of pSurfaceFormatCount is less than the number of format tuples supported, at most pSurfaceFormatCount structures will be written. If pSurfaceFormatCount is smaller than the number of format tuples supported for the surface parameters described in pSurfaceInfo, INCOMPLETE will be returned instead of SUCCESS to indicate that not all the available values were returned.

Valid Usage

Valid Usage (Implicit)

  • pSurfaceInfo must be a valid pointer to a valid PhysicalDeviceSurfaceInfo2KHR structure
  • pSurfaceFormatCount must be a valid pointer to a uint32_t value
  • If the value referenced by pSurfaceFormatCount is not 0, and pSurfaceFormats is not NULL, pSurfaceFormats must be a valid pointer to an array of pSurfaceFormatCount SurfaceFormat2KHR structures

Return Codes

Success
Failure

See Also

PhysicalDevice, PhysicalDeviceSurfaceInfo2KHR, SurfaceFormat2KHR

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.1-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)))

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

VkSurfaceCapabilities2KHR - Structure describing capabilities of a surface

Valid Usage (Implicit)

See Also

StructureType, SurfaceCapabilitiesKHR, getPhysicalDeviceSurfaceCapabilities2KHR

Constructors

SurfaceCapabilities2KHR 

Fields

Instances

Instances details
Extensible SurfaceCapabilities2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Generic (SurfaceCapabilities2KHR es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Associated Types

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

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

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

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

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

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

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

type Rep (SurfaceCapabilities2KHR es) Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

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

data SurfaceFormat2KHR Source #

VkSurfaceFormat2KHR - Structure describing a supported swapchain format tuple

Valid Usage (Implicit)

See Also

StructureType, SurfaceFormatKHR, getPhysicalDeviceSurfaceFormats2KHR

Constructors

SurfaceFormat2KHR 

Fields

Instances

Instances details
Show SurfaceFormat2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Generic SurfaceFormat2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Associated Types

type Rep SurfaceFormat2KHR :: Type -> Type #

FromCStruct SurfaceFormat2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

ToCStruct SurfaceFormat2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

Zero SurfaceFormat2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

type Rep SurfaceFormat2KHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_get_surface_capabilities2

type Rep SurfaceFormat2KHR = D1 ('MetaData "SurfaceFormat2KHR" "Vulkan.Extensions.VK_KHR_get_surface_capabilities2" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "SurfaceFormat2KHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "surfaceFormat") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 SurfaceFormatKHR)))

type KHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME = "VK_KHR_get_surface_capabilities2" 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

data SurfaceCapabilitiesKHR Source #

VkSurfaceCapabilitiesKHR - Structure describing capabilities of a surface

Description

Note

Supported usage flags of a presentable image when using PRESENT_MODE_SHARED_DEMAND_REFRESH_KHR or PRESENT_MODE_SHARED_CONTINUOUS_REFRESH_KHR presentation mode are provided by SharedPresentSurfaceCapabilitiesKHR::sharedPresentSupportedUsageFlags.

Note

Formulas such as min(N, maxImageCount) are not correct, since maxImageCount may be zero.

See Also

CompositeAlphaFlagsKHR, Extent2D, ImageUsageFlags, SurfaceCapabilities2KHR, SurfaceTransformFlagBitsKHR, SurfaceTransformFlagsKHR, getPhysicalDeviceSurfaceCapabilitiesKHR

Constructors

SurfaceCapabilitiesKHR 

Fields

  • minImageCount :: Word32

    minImageCount is the minimum number of images the specified device supports for a swapchain created for the surface, and will be at least one.

  • maxImageCount :: Word32

    maxImageCount is the maximum number of images the specified device supports for a swapchain created for the surface, and will be either 0, or greater than or equal to minImageCount. A value of 0 means that there is no limit on the number of images, though there may be limits related to the total amount of memory used by presentable images.

  • currentExtent :: Extent2D

    currentExtent is the current width and height of the surface, or the special value (0xFFFFFFFF, 0xFFFFFFFF) indicating that the surface size will be determined by the extent of a swapchain targeting the surface.

  • minImageExtent :: Extent2D

    minImageExtent contains the smallest valid swapchain extent for the surface on the specified device. The width and height of the extent will each be less than or equal to the corresponding width and height of currentExtent, unless currentExtent has the special value described above.

  • maxImageExtent :: Extent2D

    maxImageExtent contains the largest valid swapchain extent for the surface on the specified device. The width and height of the extent will each be greater than or equal to the corresponding width and height of minImageExtent. The width and height of the extent will each be greater than or equal to the corresponding width and height of currentExtent, unless currentExtent has the special value described above.

  • maxImageArrayLayers :: Word32

    maxImageArrayLayers is the maximum number of layers presentable images can have for a swapchain created for this device and surface, and will be at least one.

  • supportedTransforms :: SurfaceTransformFlagsKHR

    supportedTransforms is a bitmask of SurfaceTransformFlagBitsKHR indicating the presentation transforms supported for the surface on the specified device. At least one bit will be set.

  • currentTransform :: SurfaceTransformFlagBitsKHR

    currentTransform is SurfaceTransformFlagBitsKHR value indicating the surface’s current transform relative to the presentation engine’s natural orientation.

  • supportedCompositeAlpha :: CompositeAlphaFlagsKHR

    supportedCompositeAlpha is a bitmask of CompositeAlphaFlagBitsKHR, representing the alpha compositing modes supported by the presentation engine for the surface on the specified device, and at least one bit will be set. Opaque composition can be achieved in any alpha compositing mode by either using an image format that has no alpha component, or by ensuring that all pixels in the presentable images have an alpha value of 1.0.

  • supportedUsageFlags :: ImageUsageFlags

    supportedUsageFlags is a bitmask of ImageUsageFlagBits representing the ways the application can use the presentable images of a swapchain created with PresentModeKHR set to PRESENT_MODE_IMMEDIATE_KHR, PRESENT_MODE_MAILBOX_KHR, PRESENT_MODE_FIFO_KHR or PRESENT_MODE_FIFO_RELAXED_KHR for the surface on the specified device. IMAGE_USAGE_COLOR_ATTACHMENT_BIT must be included in the set but implementations may support additional usages.

Instances

Instances details
Show SurfaceCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Generic SurfaceCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Associated Types

type Rep SurfaceCapabilitiesKHR :: Type -> Type #

FromCStruct SurfaceCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

ToCStruct SurfaceCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Zero SurfaceCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

type Rep SurfaceCapabilitiesKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

data SurfaceFormatKHR Source #

VkSurfaceFormatKHR - Structure describing a supported swapchain format-color space pair

See Also

ColorSpaceKHR, Format, SurfaceFormat2KHR, getPhysicalDeviceSurfaceFormatsKHR

Constructors

SurfaceFormatKHR 

Fields

Instances

Instances details
Eq SurfaceFormatKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Show SurfaceFormatKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Generic SurfaceFormatKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Associated Types

type Rep SurfaceFormatKHR :: Type -> Type #

Storable SurfaceFormatKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

FromCStruct SurfaceFormatKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

ToCStruct SurfaceFormatKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

Zero SurfaceFormatKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

type Rep SurfaceFormatKHR Source # 
Instance details

Defined in Vulkan.Extensions.VK_KHR_surface

type Rep SurfaceFormatKHR = D1 ('MetaData "SurfaceFormatKHR" "Vulkan.Extensions.VK_KHR_surface" "vulkan-3.6.1-inplace" 'False) (C1 ('MetaCons "SurfaceFormatKHR" 'PrefixI 'True) (S1 ('MetaSel ('Just "format") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Format) :*: S1 ('MetaSel ('Just "colorSpace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ColorSpaceKHR)))

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