{-# language CPP #-}
-- | = Name
--
-- VK_KHR_get_surface_capabilities2 - instance extension
--
-- == VK_KHR_get_surface_capabilities2
--
-- [__Name String__]
--     @VK_KHR_get_surface_capabilities2@
--
-- [__Extension Type__]
--     Instance extension
--
-- [__Registered Extension Number__]
--     120
--
-- [__Revision__]
--     1
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_surface@ to be enabled
--
-- [__Contact__]
--
--     -   James Jones
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_KHR_get_surface_capabilities2] @cubanismo%0A*Here describe the issue or question you have about the VK_KHR_get_surface_capabilities2 extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2017-02-27
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Ian Elliott, Google
--
--     -   James Jones, NVIDIA
--
--     -   Alon Or-bach, Samsung
--
-- == Description
--
-- This extension provides new entry points to query device surface
-- capabilities in a way that can be easily extended by other extensions,
-- without introducing any further entry points. This extension can be
-- considered the @VK_KHR_surface@ equivalent of the
-- @VK_KHR_get_physical_device_properties2@ extension.
--
-- == New Commands
--
-- -   'getPhysicalDeviceSurfaceCapabilities2KHR'
--
-- -   'getPhysicalDeviceSurfaceFormats2KHR'
--
-- == New Structures
--
-- -   'PhysicalDeviceSurfaceInfo2KHR'
--
-- -   'SurfaceCapabilities2KHR'
--
-- -   'SurfaceFormat2KHR'
--
-- == New Enum Constants
--
-- -   'KHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME'
--
-- -   'KHR_GET_SURFACE_CAPABILITIES_2_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_SURFACE_INFO_2_KHR'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SURFACE_CAPABILITIES_2_KHR'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SURFACE_FORMAT_2_KHR'
--
-- == Issues
--
-- 1) What should this extension be named?
--
-- __RESOLVED__: @VK_KHR_get_surface_capabilities2@. Other alternatives:
--
-- -   @VK_KHR_surface2@
--
-- -   One extension, combining a separate display-specific query
--     extension.
--
-- 2) Should additional WSI query functions be extended?
--
-- __RESOLVED__:
--
-- -   'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR':
--     Yes. The need for this motivated the extension.
--
-- -   'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceSupportKHR':
--     No. Currently only has boolean output. Extensions should instead
--     extend 'getPhysicalDeviceSurfaceCapabilities2KHR'.
--
-- -   'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceFormatsKHR':
--     Yes.
--
-- -   'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfacePresentModesKHR':
--     No. Recent discussion concluded this introduced too much variability
--     for applications to deal with. Extensions should instead extend
--     'getPhysicalDeviceSurfaceCapabilities2KHR'.
--
-- -   'Vulkan.Extensions.VK_KHR_xlib_surface.getPhysicalDeviceXlibPresentationSupportKHR':
--     Not in this extension.
--
-- -   'Vulkan.Extensions.VK_KHR_xcb_surface.getPhysicalDeviceXcbPresentationSupportKHR':
--     Not in this extension.
--
-- -   'Vulkan.Extensions.VK_KHR_wayland_surface.getPhysicalDeviceWaylandPresentationSupportKHR':
--     Not in this extension.
--
-- -   'Vulkan.Extensions.VK_KHR_win32_surface.getPhysicalDeviceWin32PresentationSupportKHR':
--     Not in this extension.
--
-- == Version History
--
-- -   Revision 1, 2017-02-27 (James Jones)
--
--     -   Initial draft.
--
-- == See Also
--
-- 'PhysicalDeviceSurfaceInfo2KHR', 'SurfaceCapabilities2KHR',
-- 'SurfaceFormat2KHR', 'getPhysicalDeviceSurfaceCapabilities2KHR',
-- 'getPhysicalDeviceSurfaceFormats2KHR'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_KHR_get_surface_capabilities2 Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_KHR_get_surface_capabilities2  ( getPhysicalDeviceSurfaceCapabilities2KHR
                                                           , getPhysicalDeviceSurfaceFormats2KHR
                                                           , PhysicalDeviceSurfaceInfo2KHR(..)
                                                           , SurfaceCapabilities2KHR(..)
                                                           , SurfaceFormat2KHR(..)
                                                           , KHR_GET_SURFACE_CAPABILITIES_2_SPEC_VERSION
                                                           , pattern KHR_GET_SURFACE_CAPABILITIES_2_SPEC_VERSION
                                                           , KHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME
                                                           , pattern KHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME
                                                           , SurfaceKHR(..)
                                                           , SurfaceCapabilitiesKHR(..)
                                                           , SurfaceFormatKHR(..)
                                                           , ColorSpaceKHR(..)
                                                           , CompositeAlphaFlagBitsKHR(..)
                                                           , CompositeAlphaFlagsKHR
                                                           , SurfaceTransformFlagBitsKHR(..)
                                                           , SurfaceTransformFlagsKHR
                                                           ) where

import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.NamedType ((:::))
import Vulkan.CStruct.Extends (Chain)
import {-# SOURCE #-} Vulkan.Extensions.VK_AMD_display_native_hdr (DisplayNativeHdrSurfaceCapabilitiesAMD)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_image_compression_control (ImageCompressionPropertiesEXT)
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceSurfaceCapabilities2KHR))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceSurfaceFormats2KHR))
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice(PhysicalDevice))
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_shared_presentable_image (SharedPresentSurfaceCapabilitiesKHR)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_full_screen_exclusive (SurfaceCapabilitiesFullScreenExclusiveEXT)
import Vulkan.Extensions.VK_KHR_surface (SurfaceCapabilitiesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_present_barrier (SurfaceCapabilitiesPresentBarrierNV)
import Vulkan.Extensions.VK_KHR_surface (SurfaceFormatKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_full_screen_exclusive (SurfaceFullScreenExclusiveInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_full_screen_exclusive (SurfaceFullScreenExclusiveWin32InfoEXT)
import Vulkan.Extensions.Handles (SurfaceKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_surface_maintenance1 (SurfacePresentModeCompatibilityEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_surface_maintenance1 (SurfacePresentModeEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_surface_maintenance1 (SurfacePresentScalingCapabilitiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_surface_protected_capabilities (SurfaceProtectedCapabilitiesKHR)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SURFACE_INFO_2_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SURFACE_CAPABILITIES_2_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SURFACE_FORMAT_2_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_KHR_surface (ColorSpaceKHR(..))
import Vulkan.Extensions.VK_KHR_surface (CompositeAlphaFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_surface (CompositeAlphaFlagsKHR)
import Vulkan.Extensions.VK_KHR_surface (SurfaceCapabilitiesKHR(..))
import Vulkan.Extensions.VK_KHR_surface (SurfaceFormatKHR(..))
import Vulkan.Extensions.Handles (SurfaceKHR(..))
import Vulkan.Extensions.VK_KHR_surface (SurfaceTransformFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_surface (SurfaceTransformFlagsKHR)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceSurfaceCapabilities2KHR
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR) -> Ptr (SomeStruct SurfaceCapabilities2KHR) -> IO Result) -> Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR) -> Ptr (SomeStruct SurfaceCapabilities2KHR) -> IO Result

-- | vkGetPhysicalDeviceSurfaceCapabilities2KHR - Reports capabilities of a
-- surface on a physical device
--
-- = Description
--
-- 'getPhysicalDeviceSurfaceCapabilities2KHR' behaves similarly to
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR',
-- with the ability to specify extended inputs via chained input
-- structures, and to return extended information via chained output
-- structures.
--
-- == Valid Usage
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-pSurfaceInfo-06521#
--     If the @VK_GOOGLE_surfaceless_query@ extension is not enabled,
--     @pSurfaceInfo->surface@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SurfaceKHR' handle
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-pSurfaceInfo-06522#
--     If @pSurfaceInfo->surface@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', it /must/ be supported by
--     @physicalDevice@, as reported by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceSupportKHR'
--     or an equivalent platform-specific mechanism
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-pNext-02671# If a
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceCapabilitiesFullScreenExclusiveEXT'
--     structure is included in the @pNext@ chain of
--     @pSurfaceCapabilities@, a
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceFullScreenExclusiveWin32InfoEXT'
--     structure /must/ be included in the @pNext@ chain of @pSurfaceInfo@
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-pNext-07776# If a
--     'Vulkan.Extensions.VK_EXT_surface_maintenance1.SurfacePresentModeCompatibilityEXT'
--     structure is included in the @pNext@ chain of
--     @pSurfaceCapabilities@, a
--     'Vulkan.Extensions.VK_EXT_surface_maintenance1.SurfacePresentModeEXT'
--     structure /must/ be included in the @pNext@ chain of @pSurfaceInfo@
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-pNext-07777# If a
--     'Vulkan.Extensions.VK_EXT_surface_maintenance1.SurfacePresentScalingCapabilitiesEXT'
--     structure is included in the @pNext@ chain of
--     @pSurfaceCapabilities@, a
--     'Vulkan.Extensions.VK_EXT_surface_maintenance1.SurfacePresentModeEXT'
--     structure /must/ be included in the @pNext@ chain of @pSurfaceInfo@
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-pNext-07778# If a
--     'Vulkan.Extensions.VK_EXT_surface_maintenance1.SurfacePresentModeCompatibilityEXT'
--     structure is included in the @pNext@ chain of
--     @pSurfaceCapabilities@, @pSurfaceInfo->surface@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SurfaceKHR' handle
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-pNext-07779# If a
--     'Vulkan.Extensions.VK_EXT_surface_maintenance1.SurfacePresentScalingCapabilitiesEXT'
--     structure is included in the @pNext@ chain of
--     @pSurfaceCapabilities@, @pSurfaceInfo->surface@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SurfaceKHR' handle
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-physicalDevice-parameter#
--     @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-pSurfaceInfo-parameter#
--     @pSurfaceInfo@ /must/ be a valid pointer to a valid
--     'PhysicalDeviceSurfaceInfo2KHR' structure
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceCapabilities2KHR-pSurfaceCapabilities-parameter#
--     @pSurfaceCapabilities@ /must/ be a valid pointer to a
--     'SurfaceCapabilities2KHR' structure
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_SURFACE_LOST_KHR'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_surface_capabilities2 VK_KHR_get_surface_capabilities2>,
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'PhysicalDeviceSurfaceInfo2KHR',
-- 'SurfaceCapabilities2KHR'
getPhysicalDeviceSurfaceCapabilities2KHR :: forall a b io
                                          . ( Extendss PhysicalDeviceSurfaceInfo2KHR a
                                            , PokeChain a
                                            , Extendss SurfaceCapabilities2KHR b
                                            , PokeChain b
                                            , PeekChain b
                                            , MonadIO io )
                                         => -- | @physicalDevice@ is the physical device that will be associated with the
                                            -- swapchain to be created, as described for
                                            -- 'Vulkan.Extensions.VK_KHR_swapchain.createSwapchainKHR'.
                                            PhysicalDevice
                                         -> -- | @pSurfaceInfo@ is a pointer to a 'PhysicalDeviceSurfaceInfo2KHR'
                                            -- structure describing the surface and other fixed parameters that would
                                            -- be consumed by 'Vulkan.Extensions.VK_KHR_swapchain.createSwapchainKHR'.
                                            (PhysicalDeviceSurfaceInfo2KHR a)
                                         -> io (SurfaceCapabilities2KHR b)
getPhysicalDeviceSurfaceCapabilities2KHR :: forall (a :: [*]) (b :: [*]) (io :: * -> *).
(Extendss PhysicalDeviceSurfaceInfo2KHR a, PokeChain a,
 Extendss SurfaceCapabilities2KHR b, PokeChain b, PeekChain b,
 MonadIO io) =>
PhysicalDevice
-> PhysicalDeviceSurfaceInfo2KHR a
-> io (SurfaceCapabilities2KHR b)
getPhysicalDeviceSurfaceCapabilities2KHR PhysicalDevice
physicalDevice
                                           PhysicalDeviceSurfaceInfo2KHR a
surfaceInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceSurfaceCapabilities2KHRPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pSurfaceCapabilities"
       ::: Ptr (SomeStruct SurfaceCapabilities2KHR))
   -> IO Result)
vkGetPhysicalDeviceSurfaceCapabilities2KHRPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pSurfaceInfo"
          ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
      -> ("pSurfaceCapabilities"
          ::: Ptr (SomeStruct SurfaceCapabilities2KHR))
      -> IO Result)
pVkGetPhysicalDeviceSurfaceCapabilities2KHR (case PhysicalDevice
physicalDevice of PhysicalDevice{InstanceCmds
$sel:instanceCmds:PhysicalDevice :: PhysicalDevice -> InstanceCmds
instanceCmds :: InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pSurfaceCapabilities"
       ::: Ptr (SomeStruct SurfaceCapabilities2KHR))
   -> IO Result)
vkGetPhysicalDeviceSurfaceCapabilities2KHRPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetPhysicalDeviceSurfaceCapabilities2KHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceSurfaceCapabilities2KHR' :: Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pSurfaceCapabilities"
    ::: Ptr (SomeStruct SurfaceCapabilities2KHR))
-> IO Result
vkGetPhysicalDeviceSurfaceCapabilities2KHR' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pSurfaceCapabilities"
       ::: Ptr (SomeStruct SurfaceCapabilities2KHR))
   -> IO Result)
-> Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pSurfaceCapabilities"
    ::: Ptr (SomeStruct SurfaceCapabilities2KHR))
-> IO Result
mkVkGetPhysicalDeviceSurfaceCapabilities2KHR FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pSurfaceCapabilities"
       ::: Ptr (SomeStruct SurfaceCapabilities2KHR))
   -> IO Result)
vkGetPhysicalDeviceSurfaceCapabilities2KHRPtr
  Ptr (PhysicalDeviceSurfaceInfo2KHR a)
pSurfaceInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PhysicalDeviceSurfaceInfo2KHR a
surfaceInfo)
  Ptr (SurfaceCapabilities2KHR b)
pPSurfaceCapabilities <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(SurfaceCapabilities2KHR _))
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDeviceSurfaceCapabilities2KHR" (Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pSurfaceCapabilities"
    ::: Ptr (SomeStruct SurfaceCapabilities2KHR))
-> IO Result
vkGetPhysicalDeviceSurfaceCapabilities2KHR'
                                                                               (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice))
                                                                               (forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (PhysicalDeviceSurfaceInfo2KHR a)
pSurfaceInfo)
                                                                               (forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (SurfaceCapabilities2KHR b)
pPSurfaceCapabilities)))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  SurfaceCapabilities2KHR b
pSurfaceCapabilities <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(SurfaceCapabilities2KHR _) Ptr (SurfaceCapabilities2KHR b)
pPSurfaceCapabilities
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (SurfaceCapabilities2KHR b
pSurfaceCapabilities)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceSurfaceFormats2KHR
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR) -> Ptr Word32 -> Ptr (SomeStruct SurfaceFormat2KHR) -> IO Result) -> Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR) -> Ptr Word32 -> Ptr (SomeStruct SurfaceFormat2KHR) -> IO Result

-- | vkGetPhysicalDeviceSurfaceFormats2KHR - Query color formats supported by
-- surface
--
-- = Description
--
-- 'getPhysicalDeviceSurfaceFormats2KHR' behaves similarly to
-- 'Vulkan.Extensions.VK_KHR_surface.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, and
-- 'Vulkan.Core10.Enums.Result.INCOMPLETE' will be returned instead of
-- 'Vulkan.Core10.Enums.Result.SUCCESS', to indicate that not all the
-- available values were returned.
--
-- == Valid Usage
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceFormats2KHR-pSurfaceInfo-06521# If
--     the @VK_GOOGLE_surfaceless_query@ extension is not enabled,
--     @pSurfaceInfo->surface@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SurfaceKHR' handle
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceFormats2KHR-pSurfaceInfo-06522# If
--     @pSurfaceInfo->surface@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', it /must/ be supported by
--     @physicalDevice@, as reported by
--     'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceSupportKHR'
--     or an equivalent platform-specific mechanism
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceFormats2KHR-physicalDevice-parameter#
--     @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceFormats2KHR-pSurfaceInfo-parameter#
--     @pSurfaceInfo@ /must/ be a valid pointer to a valid
--     'PhysicalDeviceSurfaceInfo2KHR' structure
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceFormats2KHR-pSurfaceFormatCount-parameter#
--     @pSurfaceFormatCount@ /must/ be a valid pointer to a @uint32_t@
--     value
--
-- -   #VUID-vkGetPhysicalDeviceSurfaceFormats2KHR-pSurfaceFormats-parameter#
--     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
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.INCOMPLETE'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_SURFACE_LOST_KHR'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_surface_capabilities2 VK_KHR_get_surface_capabilities2>,
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'PhysicalDeviceSurfaceInfo2KHR',
-- 'SurfaceFormat2KHR'
getPhysicalDeviceSurfaceFormats2KHR :: forall a b io
                                     . ( Extendss PhysicalDeviceSurfaceInfo2KHR a
                                       , PokeChain a
                                       , Extendss SurfaceFormat2KHR b
                                       , PokeChain b
                                       , PeekChain b
                                       , MonadIO io )
                                    => -- | @physicalDevice@ is the physical device that will be associated with the
                                       -- swapchain to be created, as described for
                                       -- 'Vulkan.Extensions.VK_KHR_swapchain.createSwapchainKHR'.
                                       PhysicalDevice
                                    -> -- | @pSurfaceInfo@ is a pointer to a 'PhysicalDeviceSurfaceInfo2KHR'
                                       -- structure describing the surface and other fixed parameters that would
                                       -- be consumed by 'Vulkan.Extensions.VK_KHR_swapchain.createSwapchainKHR'.
                                       (PhysicalDeviceSurfaceInfo2KHR a)
                                    -> io (Result, ("surfaceFormats" ::: Vector (SurfaceFormat2KHR b)))
getPhysicalDeviceSurfaceFormats2KHR :: forall (a :: [*]) (b :: [*]) (io :: * -> *).
(Extendss PhysicalDeviceSurfaceInfo2KHR a, PokeChain a,
 Extendss SurfaceFormat2KHR b, PokeChain b, PeekChain b,
 MonadIO io) =>
PhysicalDevice
-> PhysicalDeviceSurfaceInfo2KHR a
-> io (Result, "surfaceFormats" ::: Vector (SurfaceFormat2KHR b))
getPhysicalDeviceSurfaceFormats2KHR PhysicalDevice
physicalDevice
                                      PhysicalDeviceSurfaceInfo2KHR a
surfaceInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceSurfaceFormats2KHRPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pSurfaceFormatCount" ::: Ptr Word32)
   -> ("pSurfaceFormats" ::: Ptr (SomeStruct SurfaceFormat2KHR))
   -> IO Result)
vkGetPhysicalDeviceSurfaceFormats2KHRPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pSurfaceInfo"
          ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
      -> ("pSurfaceFormatCount" ::: Ptr Word32)
      -> ("pSurfaceFormats" ::: Ptr (SomeStruct SurfaceFormat2KHR))
      -> IO Result)
pVkGetPhysicalDeviceSurfaceFormats2KHR (case PhysicalDevice
physicalDevice of PhysicalDevice{InstanceCmds
instanceCmds :: InstanceCmds
$sel:instanceCmds:PhysicalDevice :: PhysicalDevice -> InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pSurfaceFormatCount" ::: Ptr Word32)
   -> ("pSurfaceFormats" ::: Ptr (SomeStruct SurfaceFormat2KHR))
   -> IO Result)
vkGetPhysicalDeviceSurfaceFormats2KHRPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetPhysicalDeviceSurfaceFormats2KHR is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceSurfaceFormats2KHR' :: Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pSurfaceFormatCount" ::: Ptr Word32)
-> ("pSurfaceFormats" ::: Ptr (SomeStruct SurfaceFormat2KHR))
-> IO Result
vkGetPhysicalDeviceSurfaceFormats2KHR' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pSurfaceFormatCount" ::: Ptr Word32)
   -> ("pSurfaceFormats" ::: Ptr (SomeStruct SurfaceFormat2KHR))
   -> IO Result)
-> Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pSurfaceFormatCount" ::: Ptr Word32)
-> ("pSurfaceFormats" ::: Ptr (SomeStruct SurfaceFormat2KHR))
-> IO Result
mkVkGetPhysicalDeviceSurfaceFormats2KHR FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pSurfaceFormatCount" ::: Ptr Word32)
   -> ("pSurfaceFormats" ::: Ptr (SomeStruct SurfaceFormat2KHR))
   -> IO Result)
vkGetPhysicalDeviceSurfaceFormats2KHRPtr
  let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
  Ptr (PhysicalDeviceSurfaceInfo2KHR a)
pSurfaceInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PhysicalDeviceSurfaceInfo2KHR a
surfaceInfo)
  let x9 :: "pSurfaceInfo" ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR)
x9 = forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (PhysicalDeviceSurfaceInfo2KHR a)
pSurfaceInfo
  "pSurfaceFormatCount" ::: Ptr Word32
pPSurfaceFormatCount <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Word32 Int
4) forall a. Ptr a -> IO ()
free
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDeviceSurfaceFormats2KHR" (Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pSurfaceFormatCount" ::: Ptr Word32)
-> ("pSurfaceFormats" ::: Ptr (SomeStruct SurfaceFormat2KHR))
-> IO Result
vkGetPhysicalDeviceSurfaceFormats2KHR'
                                                                          Ptr PhysicalDevice_T
physicalDevice'
                                                                          "pSurfaceInfo" ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR)
x9
                                                                          ("pSurfaceFormatCount" ::: Ptr Word32
pPSurfaceFormatCount)
                                                                          (forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (forall a. Ptr a
nullPtr)))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Word32
pSurfaceFormatCount <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSurfaceFormatCount" ::: Ptr Word32
pPSurfaceFormatCount
  Ptr (SurfaceFormat2KHR b)
pPSurfaceFormats <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @(SurfaceFormat2KHR _) ((forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pSurfaceFormatCount)) forall a. Num a => a -> a -> a
* Int
24)) forall a. Ptr a -> IO ()
free
  [()]
_ <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\Int
i -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct (Ptr (SurfaceFormat2KHR b)
pPSurfaceFormats forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i forall a. Num a => a -> a -> a
* Int
24) :: Ptr (SurfaceFormat2KHR _)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())) [Int
0..(forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pSurfaceFormatCount)) forall a. Num a => a -> a -> a
- Int
1]
  Result
r' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDeviceSurfaceFormats2KHR" (Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pSurfaceFormatCount" ::: Ptr Word32)
-> ("pSurfaceFormats" ::: Ptr (SomeStruct SurfaceFormat2KHR))
-> IO Result
vkGetPhysicalDeviceSurfaceFormats2KHR'
                                                                           Ptr PhysicalDevice_T
physicalDevice'
                                                                           "pSurfaceInfo" ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR)
x9
                                                                           ("pSurfaceFormatCount" ::: Ptr Word32
pPSurfaceFormatCount)
                                                                           (forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (SurfaceFormat2KHR b)
pPSurfaceFormats))))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
  Word32
pSurfaceFormatCount' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word32 "pSurfaceFormatCount" ::: Ptr Word32
pPSurfaceFormatCount
  "surfaceFormats" ::: Vector (SurfaceFormat2KHR b)
pSurfaceFormats' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pSurfaceFormatCount')) (\Int
i -> forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(SurfaceFormat2KHR _) (((Ptr (SurfaceFormat2KHR b)
pPSurfaceFormats) forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
24 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (SurfaceFormat2KHR _))))
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ((Result
r'), "surfaceFormats" ::: Vector (SurfaceFormat2KHR b)
pSurfaceFormats')


-- | VkPhysicalDeviceSurfaceInfo2KHR - Structure specifying a surface and
-- related swapchain creation parameters
--
-- = Description
--
-- The members of 'PhysicalDeviceSurfaceInfo2KHR' correspond to the
-- arguments to
-- 'Vulkan.Extensions.VK_KHR_surface.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
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.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
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.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
-- 'Vulkan.Extensions.VK_KHR_swapchain.SwapchainCreateInfoKHR'.
--
-- == Valid Usage
--
-- -   #VUID-VkPhysicalDeviceSurfaceInfo2KHR-pNext-02672# If the @pNext@
--     chain includes a
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceFullScreenExclusiveInfoEXT'
--     structure with its @fullScreenExclusive@ member set to
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT',
--     and @surface@ was created using
--     'Vulkan.Extensions.VK_KHR_win32_surface.createWin32SurfaceKHR', a
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceFullScreenExclusiveWin32InfoEXT'
--     structure /must/ be included in the @pNext@ chain
--
-- -   #VUID-VkPhysicalDeviceSurfaceInfo2KHR-pSurfaceInfo-06526# When
--     passed as the @pSurfaceInfo@ parameter of
--     'getPhysicalDeviceSurfaceCapabilities2KHR', if the
--     @VK_GOOGLE_surfaceless_query@ extension is enabled and the @pNext@
--     chain of the @pSurfaceCapabilities@ parameter includes
--     'Vulkan.Extensions.VK_KHR_surface_protected_capabilities.SurfaceProtectedCapabilitiesKHR',
--     then @surface@ /can/ be 'Vulkan.Core10.APIConstants.NULL_HANDLE'.
--     Otherwise, @surface@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SurfaceKHR' handle
--
-- -   #VUID-VkPhysicalDeviceSurfaceInfo2KHR-pSurfaceInfo-06527# When
--     passed as the @pSurfaceInfo@ parameter of
--     'getPhysicalDeviceSurfaceFormats2KHR', if the
--     @VK_GOOGLE_surfaceless_query@ extension is enabled, then @surface@
--     /can/ be 'Vulkan.Core10.APIConstants.NULL_HANDLE'. Otherwise,
--     @surface@ /must/ be a valid 'Vulkan.Extensions.Handles.SurfaceKHR'
--     handle
--
-- -   #VUID-VkPhysicalDeviceSurfaceInfo2KHR-pSurfaceInfo-06528# When
--     passed as the @pSurfaceInfo@ parameter of
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.getPhysicalDeviceSurfacePresentModes2EXT',
--     if the @VK_GOOGLE_surfaceless_query@ extension is enabled, then
--     @surface@ /can/ be 'Vulkan.Core10.APIConstants.NULL_HANDLE'.
--     Otherwise, @surface@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SurfaceKHR' handle
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkPhysicalDeviceSurfaceInfo2KHR-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_SURFACE_INFO_2_KHR'
--
-- -   #VUID-VkPhysicalDeviceSurfaceInfo2KHR-pNext-pNext# Each @pNext@
--     member of any structure (including this one) in the @pNext@ chain
--     /must/ be either @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceFullScreenExclusiveInfoEXT',
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceFullScreenExclusiveWin32InfoEXT',
--     or
--     'Vulkan.Extensions.VK_EXT_surface_maintenance1.SurfacePresentModeEXT'
--
-- -   #VUID-VkPhysicalDeviceSurfaceInfo2KHR-sType-unique# The @sType@
--     value of each struct in the @pNext@ chain /must/ be unique
--
-- -   #VUID-VkPhysicalDeviceSurfaceInfo2KHR-surface-parameter# If
--     @surface@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @surface@
--     /must/ be a valid 'Vulkan.Extensions.Handles.SurfaceKHR' handle
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_surface_capabilities2 VK_KHR_get_surface_capabilities2>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Extensions.Handles.SurfaceKHR',
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.getDeviceGroupSurfacePresentModes2EXT',
-- 'getPhysicalDeviceSurfaceCapabilities2KHR',
-- 'getPhysicalDeviceSurfaceFormats2KHR',
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.getPhysicalDeviceSurfacePresentModes2EXT'
data PhysicalDeviceSurfaceInfo2KHR (es :: [Type]) = PhysicalDeviceSurfaceInfo2KHR
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    forall (es :: [*]). PhysicalDeviceSurfaceInfo2KHR es -> Chain es
next :: Chain es
  , -- | @surface@ is the surface that will be associated with the swapchain.
    forall (es :: [*]). PhysicalDeviceSurfaceInfo2KHR es -> SurfaceKHR
surface :: SurfaceKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSurfaceInfo2KHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PhysicalDeviceSurfaceInfo2KHR es)

instance Extensible PhysicalDeviceSurfaceInfo2KHR where
  extensibleTypeName :: String
extensibleTypeName = String
"PhysicalDeviceSurfaceInfo2KHR"
  setNext :: forall (ds :: [*]) (es :: [*]).
PhysicalDeviceSurfaceInfo2KHR ds
-> Chain es -> PhysicalDeviceSurfaceInfo2KHR es
setNext PhysicalDeviceSurfaceInfo2KHR{Chain ds
SurfaceKHR
surface :: SurfaceKHR
next :: Chain ds
$sel:surface:PhysicalDeviceSurfaceInfo2KHR :: forall (es :: [*]). PhysicalDeviceSurfaceInfo2KHR es -> SurfaceKHR
$sel:next:PhysicalDeviceSurfaceInfo2KHR :: forall (es :: [*]). PhysicalDeviceSurfaceInfo2KHR es -> Chain es
..} Chain es
next' = PhysicalDeviceSurfaceInfo2KHR{$sel:next:PhysicalDeviceSurfaceInfo2KHR :: Chain es
next = Chain es
next', SurfaceKHR
surface :: SurfaceKHR
$sel:surface:PhysicalDeviceSurfaceInfo2KHR :: SurfaceKHR
..}
  getNext :: forall (es :: [*]). PhysicalDeviceSurfaceInfo2KHR es -> Chain es
getNext PhysicalDeviceSurfaceInfo2KHR{Chain es
SurfaceKHR
surface :: SurfaceKHR
next :: Chain es
$sel:surface:PhysicalDeviceSurfaceInfo2KHR :: forall (es :: [*]). PhysicalDeviceSurfaceInfo2KHR es -> SurfaceKHR
$sel:next:PhysicalDeviceSurfaceInfo2KHR :: forall (es :: [*]). PhysicalDeviceSurfaceInfo2KHR es -> Chain es
..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends PhysicalDeviceSurfaceInfo2KHR e => b) -> Maybe b
  extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e
-> (Extends PhysicalDeviceSurfaceInfo2KHR e => b) -> Maybe b
extends proxy e
_ Extends PhysicalDeviceSurfaceInfo2KHR e => b
f
    | Just e :~: SurfacePresentModeEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfacePresentModeEXT = forall a. a -> Maybe a
Just Extends PhysicalDeviceSurfaceInfo2KHR e => b
f
    | Just e :~: SurfaceFullScreenExclusiveWin32InfoEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfaceFullScreenExclusiveWin32InfoEXT = forall a. a -> Maybe a
Just Extends PhysicalDeviceSurfaceInfo2KHR e => b
f
    | Just e :~: SurfaceFullScreenExclusiveInfoEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfaceFullScreenExclusiveInfoEXT = forall a. a -> Maybe a
Just Extends PhysicalDeviceSurfaceInfo2KHR e => b
f
    | Bool
otherwise = forall a. Maybe a
Nothing

instance ( Extendss PhysicalDeviceSurfaceInfo2KHR es
         , PokeChain es ) => ToCStruct (PhysicalDeviceSurfaceInfo2KHR es) where
  withCStruct :: forall b.
PhysicalDeviceSurfaceInfo2KHR es
-> (Ptr (PhysicalDeviceSurfaceInfo2KHR es) -> IO b) -> IO b
withCStruct PhysicalDeviceSurfaceInfo2KHR es
x Ptr (PhysicalDeviceSurfaceInfo2KHR es) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p PhysicalDeviceSurfaceInfo2KHR es
x (Ptr (PhysicalDeviceSurfaceInfo2KHR es) -> IO b
f Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p)
  pokeCStruct :: forall b.
Ptr (PhysicalDeviceSurfaceInfo2KHR es)
-> PhysicalDeviceSurfaceInfo2KHR es -> IO b -> IO b
pokeCStruct Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p PhysicalDeviceSurfaceInfo2KHR{Chain es
SurfaceKHR
surface :: SurfaceKHR
next :: Chain es
$sel:surface:PhysicalDeviceSurfaceInfo2KHR :: forall (es :: [*]). PhysicalDeviceSurfaceInfo2KHR es -> SurfaceKHR
$sel:next:PhysicalDeviceSurfaceInfo2KHR :: forall (es :: [*]). PhysicalDeviceSurfaceInfo2KHR es -> Chain es
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SURFACE_INFO_2_KHR)
    Ptr ()
pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceKHR)) (SurfaceKHR
surface)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr (PhysicalDeviceSurfaceInfo2KHR es) -> IO b -> IO b
pokeZeroCStruct Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SURFACE_INFO_2_KHR)
    Ptr ()
pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f

instance ( Extendss PhysicalDeviceSurfaceInfo2KHR es
         , PeekChain es ) => FromCStruct (PhysicalDeviceSurfaceInfo2KHR es) where
  peekCStruct :: Ptr (PhysicalDeviceSurfaceInfo2KHR es)
-> IO (PhysicalDeviceSurfaceInfo2KHR es)
peekCStruct Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p = do
    Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ())))
    Chain es
next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    SurfaceKHR
surface <- forall a. Storable a => Ptr a -> IO a
peek @SurfaceKHR ((Ptr (PhysicalDeviceSurfaceInfo2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceKHR))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (es :: [*]).
Chain es -> SurfaceKHR -> PhysicalDeviceSurfaceInfo2KHR es
PhysicalDeviceSurfaceInfo2KHR
             Chain es
next SurfaceKHR
surface

instance es ~ '[] => Zero (PhysicalDeviceSurfaceInfo2KHR es) where
  zero :: PhysicalDeviceSurfaceInfo2KHR es
zero = forall (es :: [*]).
Chain es -> SurfaceKHR -> PhysicalDeviceSurfaceInfo2KHR es
PhysicalDeviceSurfaceInfo2KHR
           ()
           forall a. Zero a => a
zero


-- | VkSurfaceCapabilities2KHR - Structure describing capabilities of a
-- surface
--
-- = Description
--
-- If the @VK_GOOGLE_surfaceless_query@ extension is enabled and
-- 'PhysicalDeviceSurfaceInfo2KHR'::@surface@ in the
-- 'getPhysicalDeviceSurfaceCapabilities2KHR' call is
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE', the values returned in
-- @minImageCount@, @maxImageCount@, @currentExtent@, and
-- @currentTransform@ will not reflect that of any surface and will instead
-- be as such:
--
-- -   @minImageCount@ and @maxImageCount@ will be 0xFFFFFFFF
--
-- -   @currentExtent@ will be (0xFFFFFFFF, 0xFFFFFFFF)
--
-- -   @currentTransform@ will be
--     'Vulkan.Extensions.VK_KHR_surface.SURFACE_TRANSFORM_INHERIT_BIT_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkSurfaceCapabilities2KHR-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SURFACE_CAPABILITIES_2_KHR'
--
-- -   #VUID-VkSurfaceCapabilities2KHR-pNext-pNext# Each @pNext@ member of
--     any structure (including this one) in the @pNext@ chain /must/ be
--     either @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_AMD_display_native_hdr.DisplayNativeHdrSurfaceCapabilitiesAMD',
--     'Vulkan.Extensions.VK_KHR_shared_presentable_image.SharedPresentSurfaceCapabilitiesKHR',
--     'Vulkan.Extensions.VK_EXT_full_screen_exclusive.SurfaceCapabilitiesFullScreenExclusiveEXT',
--     'Vulkan.Extensions.VK_NV_present_barrier.SurfaceCapabilitiesPresentBarrierNV',
--     'Vulkan.Extensions.VK_EXT_surface_maintenance1.SurfacePresentModeCompatibilityEXT',
--     'Vulkan.Extensions.VK_EXT_surface_maintenance1.SurfacePresentScalingCapabilitiesEXT',
--     or
--     'Vulkan.Extensions.VK_KHR_surface_protected_capabilities.SurfaceProtectedCapabilitiesKHR'
--
-- -   #VUID-VkSurfaceCapabilities2KHR-sType-unique# The @sType@ value of
--     each struct in the @pNext@ chain /must/ be unique
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_surface_capabilities2 VK_KHR_get_surface_capabilities2>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR',
-- 'getPhysicalDeviceSurfaceCapabilities2KHR'
data SurfaceCapabilities2KHR (es :: [Type]) = SurfaceCapabilities2KHR
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    forall (es :: [*]). SurfaceCapabilities2KHR es -> Chain es
next :: Chain es
  , -- | @surfaceCapabilities@ is a
    -- 'Vulkan.Extensions.VK_KHR_surface.SurfaceCapabilitiesKHR' structure
    -- describing the capabilities of the specified surface.
    forall (es :: [*]).
SurfaceCapabilities2KHR es -> SurfaceCapabilitiesKHR
surfaceCapabilities :: SurfaceCapabilitiesKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SurfaceCapabilities2KHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (SurfaceCapabilities2KHR es)

instance Extensible SurfaceCapabilities2KHR where
  extensibleTypeName :: String
extensibleTypeName = String
"SurfaceCapabilities2KHR"
  setNext :: forall (ds :: [*]) (es :: [*]).
SurfaceCapabilities2KHR ds
-> Chain es -> SurfaceCapabilities2KHR es
setNext SurfaceCapabilities2KHR{Chain ds
SurfaceCapabilitiesKHR
surfaceCapabilities :: SurfaceCapabilitiesKHR
next :: Chain ds
$sel:surfaceCapabilities:SurfaceCapabilities2KHR :: forall (es :: [*]).
SurfaceCapabilities2KHR es -> SurfaceCapabilitiesKHR
$sel:next:SurfaceCapabilities2KHR :: forall (es :: [*]). SurfaceCapabilities2KHR es -> Chain es
..} Chain es
next' = SurfaceCapabilities2KHR{$sel:next:SurfaceCapabilities2KHR :: Chain es
next = Chain es
next', SurfaceCapabilitiesKHR
surfaceCapabilities :: SurfaceCapabilitiesKHR
$sel:surfaceCapabilities:SurfaceCapabilities2KHR :: SurfaceCapabilitiesKHR
..}
  getNext :: forall (es :: [*]). SurfaceCapabilities2KHR es -> Chain es
getNext SurfaceCapabilities2KHR{Chain es
SurfaceCapabilitiesKHR
surfaceCapabilities :: SurfaceCapabilitiesKHR
next :: Chain es
$sel:surfaceCapabilities:SurfaceCapabilities2KHR :: forall (es :: [*]).
SurfaceCapabilities2KHR es -> SurfaceCapabilitiesKHR
$sel:next:SurfaceCapabilities2KHR :: forall (es :: [*]). SurfaceCapabilities2KHR es -> Chain es
..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends SurfaceCapabilities2KHR e => b) -> Maybe b
  extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e -> (Extends SurfaceCapabilities2KHR e => b) -> Maybe b
extends proxy e
_ Extends SurfaceCapabilities2KHR e => b
f
    | Just e :~: SurfacePresentModeCompatibilityEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfacePresentModeCompatibilityEXT = forall a. a -> Maybe a
Just Extends SurfaceCapabilities2KHR e => b
f
    | Just e :~: SurfacePresentScalingCapabilitiesEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfacePresentScalingCapabilitiesEXT = forall a. a -> Maybe a
Just Extends SurfaceCapabilities2KHR e => b
f
    | Just e :~: SurfaceCapabilitiesPresentBarrierNV
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfaceCapabilitiesPresentBarrierNV = forall a. a -> Maybe a
Just Extends SurfaceCapabilities2KHR e => b
f
    | Just e :~: SurfaceCapabilitiesFullScreenExclusiveEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfaceCapabilitiesFullScreenExclusiveEXT = forall a. a -> Maybe a
Just Extends SurfaceCapabilities2KHR e => b
f
    | Just e :~: SurfaceProtectedCapabilitiesKHR
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SurfaceProtectedCapabilitiesKHR = forall a. a -> Maybe a
Just Extends SurfaceCapabilities2KHR e => b
f
    | Just e :~: SharedPresentSurfaceCapabilitiesKHR
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SharedPresentSurfaceCapabilitiesKHR = forall a. a -> Maybe a
Just Extends SurfaceCapabilities2KHR e => b
f
    | Just e :~: DisplayNativeHdrSurfaceCapabilitiesAMD
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DisplayNativeHdrSurfaceCapabilitiesAMD = forall a. a -> Maybe a
Just Extends SurfaceCapabilities2KHR e => b
f
    | Bool
otherwise = forall a. Maybe a
Nothing

instance ( Extendss SurfaceCapabilities2KHR es
         , PokeChain es ) => ToCStruct (SurfaceCapabilities2KHR es) where
  withCStruct :: forall b.
SurfaceCapabilities2KHR es
-> (Ptr (SurfaceCapabilities2KHR es) -> IO b) -> IO b
withCStruct SurfaceCapabilities2KHR es
x Ptr (SurfaceCapabilities2KHR es) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
72 forall a b. (a -> b) -> a -> b
$ \Ptr (SurfaceCapabilities2KHR es)
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (SurfaceCapabilities2KHR es)
p SurfaceCapabilities2KHR es
x (Ptr (SurfaceCapabilities2KHR es) -> IO b
f Ptr (SurfaceCapabilities2KHR es)
p)
  pokeCStruct :: forall b.
Ptr (SurfaceCapabilities2KHR es)
-> SurfaceCapabilities2KHR es -> IO b -> IO b
pokeCStruct Ptr (SurfaceCapabilities2KHR es)
p SurfaceCapabilities2KHR{Chain es
SurfaceCapabilitiesKHR
surfaceCapabilities :: SurfaceCapabilitiesKHR
next :: Chain es
$sel:surfaceCapabilities:SurfaceCapabilities2KHR :: forall (es :: [*]).
SurfaceCapabilities2KHR es -> SurfaceCapabilitiesKHR
$sel:next:SurfaceCapabilities2KHR :: forall (es :: [*]). SurfaceCapabilities2KHR es -> Chain es
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceCapabilities2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_CAPABILITIES_2_KHR)
    Ptr ()
pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceCapabilities2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceCapabilities2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceCapabilitiesKHR)) (SurfaceCapabilitiesKHR
surfaceCapabilities)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
72
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr (SurfaceCapabilities2KHR es) -> IO b -> IO b
pokeZeroCStruct Ptr (SurfaceCapabilities2KHR es)
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceCapabilities2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_CAPABILITIES_2_KHR)
    Ptr ()
pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceCapabilities2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceCapabilities2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceCapabilitiesKHR)) (forall a. Zero a => a
zero)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f

instance ( Extendss SurfaceCapabilities2KHR es
         , PeekChain es ) => FromCStruct (SurfaceCapabilities2KHR es) where
  peekCStruct :: Ptr (SurfaceCapabilities2KHR es) -> IO (SurfaceCapabilities2KHR es)
peekCStruct Ptr (SurfaceCapabilities2KHR es)
p = do
    Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (SurfaceCapabilities2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ())))
    Chain es
next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    SurfaceCapabilitiesKHR
surfaceCapabilities <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SurfaceCapabilitiesKHR ((Ptr (SurfaceCapabilities2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceCapabilitiesKHR))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (es :: [*]).
Chain es -> SurfaceCapabilitiesKHR -> SurfaceCapabilities2KHR es
SurfaceCapabilities2KHR
             Chain es
next SurfaceCapabilitiesKHR
surfaceCapabilities

instance es ~ '[] => Zero (SurfaceCapabilities2KHR es) where
  zero :: SurfaceCapabilities2KHR es
zero = forall (es :: [*]).
Chain es -> SurfaceCapabilitiesKHR -> SurfaceCapabilities2KHR es
SurfaceCapabilities2KHR
           ()
           forall a. Zero a => a
zero


-- | VkSurfaceFormat2KHR - Structure describing a supported swapchain format
-- tuple
--
-- == Valid Usage
--
-- -   #VUID-VkSurfaceFormat2KHR-pNext-06750# If the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-imageCompressionControlSwapchain imageCompressionControlSwapchain>
--     feature is not enabled, the @pNext@ chain /must/ not include an
--     'Vulkan.Extensions.VK_EXT_image_compression_control.ImageCompressionPropertiesEXT'
--     structure
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkSurfaceFormat2KHR-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SURFACE_FORMAT_2_KHR'
--
-- -   #VUID-VkSurfaceFormat2KHR-pNext-pNext# @pNext@ /must/ be @NULL@ or a
--     pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_image_compression_control.ImageCompressionPropertiesEXT'
--
-- -   #VUID-VkSurfaceFormat2KHR-sType-unique# The @sType@ value of each
--     struct in the @pNext@ chain /must/ be unique
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_surface_capabilities2 VK_KHR_get_surface_capabilities2>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Extensions.VK_KHR_surface.SurfaceFormatKHR',
-- 'getPhysicalDeviceSurfaceFormats2KHR'
data SurfaceFormat2KHR (es :: [Type]) = SurfaceFormat2KHR
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    forall (es :: [*]). SurfaceFormat2KHR es -> Chain es
next :: Chain es
  , -- | @surfaceFormat@ is a 'Vulkan.Extensions.VK_KHR_surface.SurfaceFormatKHR'
    -- structure describing a format-color space pair that is compatible with
    -- the specified surface.
    forall (es :: [*]). SurfaceFormat2KHR es -> SurfaceFormatKHR
surfaceFormat :: SurfaceFormatKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SurfaceFormat2KHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (SurfaceFormat2KHR es)

instance Extensible SurfaceFormat2KHR where
  extensibleTypeName :: String
extensibleTypeName = String
"SurfaceFormat2KHR"
  setNext :: forall (ds :: [*]) (es :: [*]).
SurfaceFormat2KHR ds -> Chain es -> SurfaceFormat2KHR es
setNext SurfaceFormat2KHR{Chain ds
SurfaceFormatKHR
surfaceFormat :: SurfaceFormatKHR
next :: Chain ds
$sel:surfaceFormat:SurfaceFormat2KHR :: forall (es :: [*]). SurfaceFormat2KHR es -> SurfaceFormatKHR
$sel:next:SurfaceFormat2KHR :: forall (es :: [*]). SurfaceFormat2KHR es -> Chain es
..} Chain es
next' = SurfaceFormat2KHR{$sel:next:SurfaceFormat2KHR :: Chain es
next = Chain es
next', SurfaceFormatKHR
surfaceFormat :: SurfaceFormatKHR
$sel:surfaceFormat:SurfaceFormat2KHR :: SurfaceFormatKHR
..}
  getNext :: forall (es :: [*]). SurfaceFormat2KHR es -> Chain es
getNext SurfaceFormat2KHR{Chain es
SurfaceFormatKHR
surfaceFormat :: SurfaceFormatKHR
next :: Chain es
$sel:surfaceFormat:SurfaceFormat2KHR :: forall (es :: [*]). SurfaceFormat2KHR es -> SurfaceFormatKHR
$sel:next:SurfaceFormat2KHR :: forall (es :: [*]). SurfaceFormat2KHR es -> Chain es
..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends SurfaceFormat2KHR e => b) -> Maybe b
  extends :: forall e b (proxy :: * -> *).
Typeable e =>
proxy e -> (Extends SurfaceFormat2KHR e => b) -> Maybe b
extends proxy e
_ Extends SurfaceFormat2KHR e => b
f
    | Just e :~: ImageCompressionPropertiesEXT
Refl <- forall {k} (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageCompressionPropertiesEXT = forall a. a -> Maybe a
Just Extends SurfaceFormat2KHR e => b
f
    | Bool
otherwise = forall a. Maybe a
Nothing

instance ( Extendss SurfaceFormat2KHR es
         , PokeChain es ) => ToCStruct (SurfaceFormat2KHR es) where
  withCStruct :: forall b.
SurfaceFormat2KHR es
-> (Ptr (SurfaceFormat2KHR es) -> IO b) -> IO b
withCStruct SurfaceFormat2KHR es
x Ptr (SurfaceFormat2KHR es) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr (SurfaceFormat2KHR es)
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (SurfaceFormat2KHR es)
p SurfaceFormat2KHR es
x (Ptr (SurfaceFormat2KHR es) -> IO b
f Ptr (SurfaceFormat2KHR es)
p)
  pokeCStruct :: forall b.
Ptr (SurfaceFormat2KHR es) -> SurfaceFormat2KHR es -> IO b -> IO b
pokeCStruct Ptr (SurfaceFormat2KHR es)
p SurfaceFormat2KHR{Chain es
SurfaceFormatKHR
surfaceFormat :: SurfaceFormatKHR
next :: Chain es
$sel:surfaceFormat:SurfaceFormat2KHR :: forall (es :: [*]). SurfaceFormat2KHR es -> SurfaceFormatKHR
$sel:next:SurfaceFormat2KHR :: forall (es :: [*]). SurfaceFormat2KHR es -> Chain es
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceFormat2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_FORMAT_2_KHR)
    Ptr ()
pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceFormat2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceFormat2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceFormatKHR)) (SurfaceFormatKHR
surfaceFormat)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr (SurfaceFormat2KHR es) -> IO b -> IO b
pokeZeroCStruct Ptr (SurfaceFormat2KHR es)
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceFormat2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_FORMAT_2_KHR)
    Ptr ()
pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. Ptr a -> Ptr b
castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceFormat2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SurfaceFormat2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceFormatKHR)) (forall a. Zero a => a
zero)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f

instance ( Extendss SurfaceFormat2KHR es
         , PeekChain es ) => FromCStruct (SurfaceFormat2KHR es) where
  peekCStruct :: Ptr (SurfaceFormat2KHR es) -> IO (SurfaceFormat2KHR es)
peekCStruct Ptr (SurfaceFormat2KHR es)
p = do
    Ptr ()
pNext <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (SurfaceFormat2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ())))
    Chain es
next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    SurfaceFormatKHR
surfaceFormat <- forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SurfaceFormatKHR ((Ptr (SurfaceFormat2KHR es)
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceFormatKHR))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall (es :: [*]).
Chain es -> SurfaceFormatKHR -> SurfaceFormat2KHR es
SurfaceFormat2KHR
             Chain es
next SurfaceFormatKHR
surfaceFormat

instance es ~ '[] => Zero (SurfaceFormat2KHR es) where
  zero :: SurfaceFormat2KHR es
zero = forall (es :: [*]).
Chain es -> SurfaceFormatKHR -> SurfaceFormat2KHR es
SurfaceFormat2KHR
           ()
           forall a. Zero a => a
zero


type KHR_GET_SURFACE_CAPABILITIES_2_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_KHR_GET_SURFACE_CAPABILITIES_2_SPEC_VERSION"
pattern KHR_GET_SURFACE_CAPABILITIES_2_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_GET_SURFACE_CAPABILITIES_2_SPEC_VERSION :: forall a. Integral a => a
$mKHR_GET_SURFACE_CAPABILITIES_2_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_GET_SURFACE_CAPABILITIES_2_SPEC_VERSION = 1


type KHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME = "VK_KHR_get_surface_capabilities2"

-- No documentation found for TopLevel "VK_KHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME"
pattern KHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mKHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
KHR_GET_SURFACE_CAPABILITIES_2_EXTENSION_NAME = "VK_KHR_get_surface_capabilities2"