{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_full_screen_exclusive  ( getPhysicalDeviceSurfacePresentModes2EXT
                                                       , getDeviceGroupSurfacePresentModes2EXT
                                                       , acquireFullScreenExclusiveModeEXT
                                                       , releaseFullScreenExclusiveModeEXT
                                                       , SurfaceFullScreenExclusiveInfoEXT(..)
                                                       , SurfaceFullScreenExclusiveWin32InfoEXT(..)
                                                       , SurfaceCapabilitiesFullScreenExclusiveEXT(..)
                                                       , FullScreenExclusiveEXT( FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT
                                                                               , FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT
                                                                               , FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT
                                                                               , FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT
                                                                               , ..
                                                                               )
                                                       , EXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION
                                                       , pattern EXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION
                                                       , EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME
                                                       , pattern EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME
                                                       , HMONITOR
                                                       , SurfaceKHR(..)
                                                       , SwapchainKHR(..)
                                                       , PhysicalDeviceSurfaceInfo2KHR(..)
                                                       , PresentModeKHR(..)
                                                       , DeviceGroupPresentModeFlagBitsKHR(..)
                                                       , DeviceGroupPresentModeFlagsKHR
                                                       ) where

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import Data.Word (Word32)
import Text.Read.Lex (Lexeme(Ident))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkAcquireFullScreenExclusiveModeEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceGroupSurfacePresentModes2EXT))
import Vulkan.Dynamic (DeviceCmds(pVkReleaseFullScreenExclusiveModeEXT))
import Vulkan.Extensions.VK_KHR_swapchain (DeviceGroupPresentModeFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_swapchain (DeviceGroupPresentModeFlagsKHR)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceSurfacePresentModes2EXT))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Extensions.VK_KHR_get_surface_capabilities2 (PhysicalDeviceSurfaceInfo2KHR)
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.Extensions.VK_KHR_surface (PresentModeKHR)
import Vulkan.Extensions.VK_KHR_surface (PresentModeKHR(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.Handles (SwapchainKHR)
import Vulkan.Extensions.Handles (SwapchainKHR(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SURFACE_CAPABILITIES_FULL_SCREEN_EXCLUSIVE_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_WIN32_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_KHR_swapchain (DeviceGroupPresentModeFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_swapchain (DeviceGroupPresentModeFlagsKHR)
import Vulkan.Extensions.VK_KHR_get_surface_capabilities2 (PhysicalDeviceSurfaceInfo2KHR(..))
import Vulkan.Extensions.VK_KHR_surface (PresentModeKHR(..))
import Vulkan.Extensions.Handles (SurfaceKHR(..))
import Vulkan.Extensions.Handles (SwapchainKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceSurfacePresentModes2EXT
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR) -> Ptr Word32 -> Ptr PresentModeKHR -> IO Result) -> Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR) -> Ptr Word32 -> Ptr PresentModeKHR -> IO Result

-- | vkGetPhysicalDeviceSurfacePresentModes2EXT - Query supported
-- presentation modes
--
-- = Description
--
-- 'getPhysicalDeviceSurfacePresentModes2EXT' behaves similarly to
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfacePresentModesKHR',
-- with the ability to specify extended inputs via chained input
-- structures.
--
-- == Valid Usage (Implicit)
--
-- -   @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   @pSurfaceInfo@ /must/ be a valid pointer to a valid
--     'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.PhysicalDeviceSurfaceInfo2KHR'
--     structure
--
-- -   @pPresentModeCount@ /must/ be a valid pointer to a @uint32_t@ value
--
-- -   If the value referenced by @pPresentModeCount@ is not @0@, and
--     @pPresentModes@ is not @NULL@, @pPresentModes@ /must/ be a valid
--     pointer to an array of @pPresentModeCount@
--     'Vulkan.Extensions.VK_KHR_surface.PresentModeKHR' values
--
-- == 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
--
-- 'Vulkan.Core10.Handles.PhysicalDevice',
-- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.PhysicalDeviceSurfaceInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_surface.PresentModeKHR'
getPhysicalDeviceSurfacePresentModes2EXT :: forall a io
                                          . (Extendss PhysicalDeviceSurfaceInfo2KHR a, PokeChain a, 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
                                            -- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.PhysicalDeviceSurfaceInfo2KHR'
                                            -- structure describing the surface and other fixed parameters that would
                                            -- be consumed by 'Vulkan.Extensions.VK_KHR_swapchain.createSwapchainKHR'.
                                            (PhysicalDeviceSurfaceInfo2KHR a)
                                         -> io (Result, ("presentModes" ::: Vector PresentModeKHR))
getPhysicalDeviceSurfacePresentModes2EXT :: PhysicalDevice
-> PhysicalDeviceSurfaceInfo2KHR a
-> io (Result, "presentModes" ::: Vector PresentModeKHR)
getPhysicalDeviceSurfacePresentModes2EXT physicalDevice :: PhysicalDevice
physicalDevice surfaceInfo :: PhysicalDeviceSurfaceInfo2KHR a
surfaceInfo = IO (Result, "presentModes" ::: Vector PresentModeKHR)
-> io (Result, "presentModes" ::: Vector PresentModeKHR)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "presentModes" ::: Vector PresentModeKHR)
 -> io (Result, "presentModes" ::: Vector PresentModeKHR))
-> (ContT
      (Result, "presentModes" ::: Vector PresentModeKHR)
      IO
      (Result, "presentModes" ::: Vector PresentModeKHR)
    -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     (Result, "presentModes" ::: Vector PresentModeKHR)
-> io (Result, "presentModes" ::: Vector PresentModeKHR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "presentModes" ::: Vector PresentModeKHR)
  IO
  (Result, "presentModes" ::: Vector PresentModeKHR)
-> IO (Result, "presentModes" ::: Vector PresentModeKHR)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "presentModes" ::: Vector PresentModeKHR)
   IO
   (Result, "presentModes" ::: Vector PresentModeKHR)
 -> io (Result, "presentModes" ::: Vector PresentModeKHR))
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     (Result, "presentModes" ::: Vector PresentModeKHR)
-> io (Result, "presentModes" ::: Vector PresentModeKHR)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceSurfacePresentModes2EXTPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pPresentModeCount" ::: Ptr Word32)
   -> ("pPresentModes" ::: Ptr PresentModeKHR)
   -> IO Result)
vkGetPhysicalDeviceSurfacePresentModes2EXTPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pSurfaceInfo"
          ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
      -> ("pPresentModeCount" ::: Ptr Word32)
      -> ("pPresentModes" ::: Ptr PresentModeKHR)
      -> IO Result)
pVkGetPhysicalDeviceSurfacePresentModes2EXT (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO ()
-> ContT (Result, "presentModes" ::: Vector PresentModeKHR) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT (Result, "presentModes" ::: Vector PresentModeKHR) IO ())
-> IO ()
-> ContT (Result, "presentModes" ::: Vector PresentModeKHR) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pPresentModeCount" ::: Ptr Word32)
   -> ("pPresentModes" ::: Ptr PresentModeKHR)
   -> IO Result)
vkGetPhysicalDeviceSurfacePresentModes2EXTPtr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pPresentModeCount" ::: Ptr Word32)
   -> ("pPresentModes" ::: Ptr PresentModeKHR)
   -> IO Result)
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pSurfaceInfo"
          ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
      -> ("pPresentModeCount" ::: Ptr Word32)
      -> ("pPresentModes" ::: Ptr PresentModeKHR)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pPresentModeCount" ::: Ptr Word32)
   -> ("pPresentModes" ::: Ptr PresentModeKHR)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceSurfacePresentModes2EXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceSurfacePresentModes2EXT' :: Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pPresentModeCount" ::: Ptr Word32)
-> ("pPresentModes" ::: Ptr PresentModeKHR)
-> IO Result
vkGetPhysicalDeviceSurfacePresentModes2EXT' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pPresentModeCount" ::: Ptr Word32)
   -> ("pPresentModes" ::: Ptr PresentModeKHR)
   -> IO Result)
-> Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pPresentModeCount" ::: Ptr Word32)
-> ("pPresentModes" ::: Ptr PresentModeKHR)
-> IO Result
mkVkGetPhysicalDeviceSurfacePresentModes2EXT FunPtr
  (Ptr PhysicalDevice_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pPresentModeCount" ::: Ptr Word32)
   -> ("pPresentModes" ::: Ptr PresentModeKHR)
   -> IO Result)
vkGetPhysicalDeviceSurfacePresentModes2EXTPtr
  let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
  Ptr (PhysicalDeviceSurfaceInfo2KHR a)
pSurfaceInfo <- ((Ptr (PhysicalDeviceSurfaceInfo2KHR a)
  -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
 -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     (Ptr (PhysicalDeviceSurfaceInfo2KHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (PhysicalDeviceSurfaceInfo2KHR a)
   -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
  -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
 -> ContT
      (Result, "presentModes" ::: Vector PresentModeKHR)
      IO
      (Ptr (PhysicalDeviceSurfaceInfo2KHR a)))
-> ((Ptr (PhysicalDeviceSurfaceInfo2KHR a)
     -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
    -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     (Ptr (PhysicalDeviceSurfaceInfo2KHR a))
forall a b. (a -> b) -> a -> b
$ PhysicalDeviceSurfaceInfo2KHR a
-> (Ptr (PhysicalDeviceSurfaceInfo2KHR a)
    -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> IO (Result, "presentModes" ::: Vector PresentModeKHR)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PhysicalDeviceSurfaceInfo2KHR a
surfaceInfo)
  let x9 :: "pSurfaceInfo" ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR)
x9 = Ptr (PhysicalDeviceSurfaceInfo2KHR a)
-> "pSurfaceInfo"
   ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (PhysicalDeviceSurfaceInfo2KHR a)
pSurfaceInfo
  "pPresentModeCount" ::: Ptr Word32
pPPresentModeCount <- ((("pPresentModeCount" ::: Ptr Word32)
  -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
 -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     ("pPresentModeCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPresentModeCount" ::: Ptr Word32)
   -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
  -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
 -> ContT
      (Result, "presentModes" ::: Vector PresentModeKHR)
      IO
      ("pPresentModeCount" ::: Ptr Word32))
-> ((("pPresentModeCount" ::: Ptr Word32)
     -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
    -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     ("pPresentModeCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pPresentModeCount" ::: Ptr Word32)
-> (("pPresentModeCount" ::: Ptr Word32) -> IO ())
-> (("pPresentModeCount" ::: Ptr Word32)
    -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> IO (Result, "presentModes" ::: Vector PresentModeKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPresentModeCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pPresentModeCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT
      (Result, "presentModes" ::: Vector PresentModeKHR) IO Result)
-> IO Result
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pPresentModeCount" ::: Ptr Word32)
-> ("pPresentModes" ::: Ptr PresentModeKHR)
-> IO Result
vkGetPhysicalDeviceSurfacePresentModes2EXT' Ptr PhysicalDevice_T
physicalDevice' "pSurfaceInfo" ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR)
x9 ("pPresentModeCount" ::: Ptr Word32
pPPresentModeCount) ("pPresentModes" ::: Ptr PresentModeKHR
forall a. Ptr a
nullPtr)
  IO ()
-> ContT (Result, "presentModes" ::: Vector PresentModeKHR) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT (Result, "presentModes" ::: Vector PresentModeKHR) IO ())
-> IO ()
-> ContT (Result, "presentModes" ::: Vector PresentModeKHR) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Word32
pPresentModeCount <- IO Word32
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      (Result, "presentModes" ::: Vector PresentModeKHR) IO Word32)
-> IO Word32
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pPresentModeCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPresentModeCount" ::: Ptr Word32
pPPresentModeCount
  "pPresentModes" ::: Ptr PresentModeKHR
pPPresentModes <- ((("pPresentModes" ::: Ptr PresentModeKHR)
  -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
 -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     ("pPresentModes" ::: Ptr PresentModeKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPresentModes" ::: Ptr PresentModeKHR)
   -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
  -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
 -> ContT
      (Result, "presentModes" ::: Vector PresentModeKHR)
      IO
      ("pPresentModes" ::: Ptr PresentModeKHR))
-> ((("pPresentModes" ::: Ptr PresentModeKHR)
     -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
    -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     ("pPresentModes" ::: Ptr PresentModeKHR)
forall a b. (a -> b) -> a -> b
$ IO ("pPresentModes" ::: Ptr PresentModeKHR)
-> (("pPresentModes" ::: Ptr PresentModeKHR) -> IO ())
-> (("pPresentModes" ::: Ptr PresentModeKHR)
    -> IO (Result, "presentModes" ::: Vector PresentModeKHR))
-> IO (Result, "presentModes" ::: Vector PresentModeKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPresentModes" ::: Ptr PresentModeKHR)
forall a. Int -> IO (Ptr a)
callocBytes @PresentModeKHR ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPresentModeCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4)) ("pPresentModes" ::: Ptr PresentModeKHR) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r' <- IO Result
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT
      (Result, "presentModes" ::: Vector PresentModeKHR) IO Result)
-> IO Result
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pPresentModeCount" ::: Ptr Word32)
-> ("pPresentModes" ::: Ptr PresentModeKHR)
-> IO Result
vkGetPhysicalDeviceSurfacePresentModes2EXT' Ptr PhysicalDevice_T
physicalDevice' "pSurfaceInfo" ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR)
x9 ("pPresentModeCount" ::: Ptr Word32
pPPresentModeCount) ("pPresentModes" ::: Ptr PresentModeKHR
pPPresentModes)
  IO ()
-> ContT (Result, "presentModes" ::: Vector PresentModeKHR) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT (Result, "presentModes" ::: Vector PresentModeKHR) IO ())
-> IO ()
-> ContT (Result, "presentModes" ::: Vector PresentModeKHR) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
  Word32
pPresentModeCount' <- IO Word32
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      (Result, "presentModes" ::: Vector PresentModeKHR) IO Word32)
-> IO Word32
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pPresentModeCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pPresentModeCount" ::: Ptr Word32
pPPresentModeCount
  "presentModes" ::: Vector PresentModeKHR
pPresentModes' <- IO ("presentModes" ::: Vector PresentModeKHR)
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     ("presentModes" ::: Vector PresentModeKHR)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("presentModes" ::: Vector PresentModeKHR)
 -> ContT
      (Result, "presentModes" ::: Vector PresentModeKHR)
      IO
      ("presentModes" ::: Vector PresentModeKHR))
-> IO ("presentModes" ::: Vector PresentModeKHR)
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     ("presentModes" ::: Vector PresentModeKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO PresentModeKHR)
-> IO ("presentModes" ::: Vector PresentModeKHR)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPresentModeCount')) (\i :: Int
i -> ("pPresentModes" ::: Ptr PresentModeKHR) -> IO PresentModeKHR
forall a. Storable a => Ptr a -> IO a
peek @PresentModeKHR (("pPresentModes" ::: Ptr PresentModeKHR
pPPresentModes ("pPresentModes" ::: Ptr PresentModeKHR)
-> Int -> "pPresentModes" ::: Ptr PresentModeKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PresentModeKHR)))
  (Result, "presentModes" ::: Vector PresentModeKHR)
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     (Result, "presentModes" ::: Vector PresentModeKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "presentModes" ::: Vector PresentModeKHR)
 -> ContT
      (Result, "presentModes" ::: Vector PresentModeKHR)
      IO
      (Result, "presentModes" ::: Vector PresentModeKHR))
-> (Result, "presentModes" ::: Vector PresentModeKHR)
-> ContT
     (Result, "presentModes" ::: Vector PresentModeKHR)
     IO
     (Result, "presentModes" ::: Vector PresentModeKHR)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "presentModes" ::: Vector PresentModeKHR
pPresentModes')


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetDeviceGroupSurfacePresentModes2EXT
  :: FunPtr (Ptr Device_T -> Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR) -> Ptr DeviceGroupPresentModeFlagsKHR -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR) -> Ptr DeviceGroupPresentModeFlagsKHR -> IO Result

-- | vkGetDeviceGroupSurfacePresentModes2EXT - Query device group present
-- capabilities for a surface
--
-- = Description
--
-- 'getDeviceGroupSurfacePresentModes2EXT' behaves similarly to
-- 'Vulkan.Extensions.VK_KHR_swapchain.getDeviceGroupSurfacePresentModesKHR',
-- with the ability to specify extended inputs via chained input
-- structures.
--
-- == 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
--
-- 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Extensions.VK_KHR_swapchain.DeviceGroupPresentModeFlagsKHR',
-- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.PhysicalDeviceSurfaceInfo2KHR'
getDeviceGroupSurfacePresentModes2EXT :: forall a io
                                       . (Extendss PhysicalDeviceSurfaceInfo2KHR a, PokeChain a, MonadIO io)
                                      => -- | @device@ is the logical device.
                                         --
                                         -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                         Device
                                      -> -- | @pSurfaceInfo@ is a pointer to a
                                         -- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.PhysicalDeviceSurfaceInfo2KHR'
                                         -- structure describing the surface and other fixed parameters that would
                                         -- be consumed by 'Vulkan.Extensions.VK_KHR_swapchain.createSwapchainKHR'.
                                         --
                                         -- @pSurfaceInfo@ /must/ be a valid pointer to a valid
                                         -- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.PhysicalDeviceSurfaceInfo2KHR'
                                         -- structure
                                         (PhysicalDeviceSurfaceInfo2KHR a)
                                      -> io (("modes" ::: DeviceGroupPresentModeFlagsKHR))
getDeviceGroupSurfacePresentModes2EXT :: Device
-> PhysicalDeviceSurfaceInfo2KHR a
-> io ("modes" ::: DeviceGroupPresentModeFlagsKHR)
getDeviceGroupSurfacePresentModes2EXT device :: Device
device surfaceInfo :: PhysicalDeviceSurfaceInfo2KHR a
surfaceInfo = IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> io ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> io ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> (ContT
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
      IO
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
    -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> io ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  ("modes" ::: DeviceGroupPresentModeFlagsKHR)
  IO
  ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   ("modes" ::: DeviceGroupPresentModeFlagsKHR)
   IO
   ("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> io ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> io ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetDeviceGroupSurfacePresentModes2EXTPtr :: FunPtr
  (Ptr Device_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
vkGetDeviceGroupSurfacePresentModes2EXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pSurfaceInfo"
          ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
      -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
      -> IO Result)
pVkGetDeviceGroupSurfacePresentModes2EXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ())
-> IO ()
-> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
vkGetDeviceGroupSurfacePresentModes2EXTPtr FunPtr
  (Ptr Device_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pSurfaceInfo"
          ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
      -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetDeviceGroupSurfacePresentModes2EXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeviceGroupSurfacePresentModes2EXT' :: Ptr Device_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO Result
vkGetDeviceGroupSurfacePresentModes2EXT' = FunPtr
  (Ptr Device_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
-> Ptr Device_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO Result
mkVkGetDeviceGroupSurfacePresentModes2EXT FunPtr
  (Ptr Device_T
   -> ("pSurfaceInfo"
       ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
   -> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO Result)
vkGetDeviceGroupSurfacePresentModes2EXTPtr
  Ptr (PhysicalDeviceSurfaceInfo2KHR a)
pSurfaceInfo <- ((Ptr (PhysicalDeviceSurfaceInfo2KHR a)
  -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
 -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     (Ptr (PhysicalDeviceSurfaceInfo2KHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (PhysicalDeviceSurfaceInfo2KHR a)
   -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
  -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
 -> ContT
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
      IO
      (Ptr (PhysicalDeviceSurfaceInfo2KHR a)))
-> ((Ptr (PhysicalDeviceSurfaceInfo2KHR a)
     -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     (Ptr (PhysicalDeviceSurfaceInfo2KHR a))
forall a b. (a -> b) -> a -> b
$ PhysicalDeviceSurfaceInfo2KHR a
-> (Ptr (PhysicalDeviceSurfaceInfo2KHR a)
    -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PhysicalDeviceSurfaceInfo2KHR a
surfaceInfo)
  "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
pPModes <- ((("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
  -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
 -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
   -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
  -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
 -> ContT
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
      IO
      ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)))
-> ((("pModes"
      ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
     -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
forall a b. (a -> b) -> a -> b
$ IO ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> (("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> IO ())
-> (("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
    -> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int
-> IO
     ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
forall a. Int -> IO (Ptr a)
callocBytes @DeviceGroupPresentModeFlagsKHR 4) ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO Result)
-> IO Result
-> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pSurfaceInfo"
    ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR))
-> ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO Result
vkGetDeviceGroupSurfacePresentModes2EXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (PhysicalDeviceSurfaceInfo2KHR a)
-> "pSurfaceInfo"
   ::: Ptr (SomeStruct PhysicalDeviceSurfaceInfo2KHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (PhysicalDeviceSurfaceInfo2KHR a)
pSurfaceInfo) ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
pPModes)
  IO () -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ())
-> IO ()
-> ContT ("modes" ::: DeviceGroupPresentModeFlagsKHR) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  "modes" ::: DeviceGroupPresentModeFlagsKHR
pModes <- IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> ContT
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
      IO
      ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. (a -> b) -> a -> b
$ ("pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> IO ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a. Storable a => Ptr a -> IO a
peek @DeviceGroupPresentModeFlagsKHR "pModes" ::: Ptr ("modes" ::: DeviceGroupPresentModeFlagsKHR)
pPModes
  ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("modes" ::: DeviceGroupPresentModeFlagsKHR)
 -> ContT
      ("modes" ::: DeviceGroupPresentModeFlagsKHR)
      IO
      ("modes" ::: DeviceGroupPresentModeFlagsKHR))
-> ("modes" ::: DeviceGroupPresentModeFlagsKHR)
-> ContT
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
     IO
     ("modes" ::: DeviceGroupPresentModeFlagsKHR)
forall a b. (a -> b) -> a -> b
$ ("modes" ::: DeviceGroupPresentModeFlagsKHR
pModes)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkAcquireFullScreenExclusiveModeEXT
  :: FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result) -> Ptr Device_T -> SwapchainKHR -> IO Result

-- | vkAcquireFullScreenExclusiveModeEXT - Acquire full-screen exclusive mode
-- for a swapchain
--
-- == Valid Usage
--
-- -   @swapchain@ /must/ not be in the retired state
--
-- -   @swapchain@ /must/ be a swapchain created with a
--     'SurfaceFullScreenExclusiveInfoEXT' structure, with
--     @fullScreenExclusive@ set to
--     'FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT'
--
-- -   @swapchain@ /must/ not currently have exclusive full-screen access
--
-- A return value of 'Vulkan.Core10.Enums.Result.SUCCESS' indicates that
-- the @swapchain@ successfully acquired exclusive full-screen access. The
-- swapchain will retain this exclusivity until either the application
-- releases exclusive full-screen access with
-- 'releaseFullScreenExclusiveModeEXT', destroys the swapchain, or if any
-- of the swapchain commands return
-- 'Vulkan.Core10.Enums.Result.ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT'
-- indicating that the mode was lost because of platform-specific changes.
--
-- If the swapchain was unable to acquire exclusive full-screen access to
-- the display then
-- 'Vulkan.Core10.Enums.Result.ERROR_INITIALIZATION_FAILED' is returned. An
-- application /can/ attempt to acquire exclusive full-screen access again
-- for the same swapchain even if this command fails, or if
-- 'Vulkan.Core10.Enums.Result.ERROR_FULL_SCREEN_EXCLUSIVE_MODE_LOST_EXT'
-- has been returned by a swapchain command.
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @swapchain@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- -   Both of @device@, and @swapchain@ /must/ have been created,
--     allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Instance'
--
-- == 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_INITIALIZATION_FAILED'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_SURFACE_LOST_KHR'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Extensions.Handles.SwapchainKHR'
acquireFullScreenExclusiveModeEXT :: forall io
                                   . (MonadIO io)
                                  => -- | @device@ is the device associated with @swapchain@.
                                     Device
                                  -> -- | @swapchain@ is the swapchain to acquire exclusive full-screen access
                                     -- for.
                                     SwapchainKHR
                                  -> io ()
acquireFullScreenExclusiveModeEXT :: Device -> SwapchainKHR -> io ()
acquireFullScreenExclusiveModeEXT device :: Device
device swapchain :: SwapchainKHR
swapchain = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkAcquireFullScreenExclusiveModeEXTPtr :: FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
vkAcquireFullScreenExclusiveModeEXTPtr = DeviceCmds -> FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
pVkAcquireFullScreenExclusiveModeEXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
vkAcquireFullScreenExclusiveModeEXTPtr FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
-> FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkAcquireFullScreenExclusiveModeEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkAcquireFullScreenExclusiveModeEXT' :: Ptr Device_T -> SwapchainKHR -> IO Result
vkAcquireFullScreenExclusiveModeEXT' = FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
-> Ptr Device_T -> SwapchainKHR -> IO Result
mkVkAcquireFullScreenExclusiveModeEXT FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
vkAcquireFullScreenExclusiveModeEXTPtr
  Result
r <- Ptr Device_T -> SwapchainKHR -> IO Result
vkAcquireFullScreenExclusiveModeEXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) (SwapchainKHR
swapchain)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkReleaseFullScreenExclusiveModeEXT
  :: FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result) -> Ptr Device_T -> SwapchainKHR -> IO Result

-- | vkReleaseFullScreenExclusiveModeEXT - Release full-screen exclusive mode
-- from a swapchain
--
-- = Description
--
-- Note
--
-- Applications will not be able to present to @swapchain@ after this call
-- until exclusive full-screen access is reacquired. This is usually useful
-- to handle when an application is minimised or otherwise intends to stop
-- presenting for a time.
--
-- == Valid Usage
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Extensions.Handles.SwapchainKHR'
releaseFullScreenExclusiveModeEXT :: forall io
                                   . (MonadIO io)
                                  => -- | @device@ is the device associated with @swapchain@.
                                     Device
                                  -> -- | @swapchain@ is the swapchain to release exclusive full-screen access
                                     -- from.
                                     --
                                     -- @swapchain@ /must/ not be in the retired state
                                     --
                                     -- @swapchain@ /must/ be a swapchain created with a
                                     -- 'SurfaceFullScreenExclusiveInfoEXT' structure, with
                                     -- @fullScreenExclusive@ set to
                                     -- 'FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT'
                                     SwapchainKHR
                                  -> io ()
releaseFullScreenExclusiveModeEXT :: Device -> SwapchainKHR -> io ()
releaseFullScreenExclusiveModeEXT device :: Device
device swapchain :: SwapchainKHR
swapchain = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkReleaseFullScreenExclusiveModeEXTPtr :: FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
vkReleaseFullScreenExclusiveModeEXTPtr = DeviceCmds -> FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
pVkReleaseFullScreenExclusiveModeEXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
vkReleaseFullScreenExclusiveModeEXTPtr FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
-> FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkReleaseFullScreenExclusiveModeEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkReleaseFullScreenExclusiveModeEXT' :: Ptr Device_T -> SwapchainKHR -> IO Result
vkReleaseFullScreenExclusiveModeEXT' = FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
-> Ptr Device_T -> SwapchainKHR -> IO Result
mkVkReleaseFullScreenExclusiveModeEXT FunPtr (Ptr Device_T -> SwapchainKHR -> IO Result)
vkReleaseFullScreenExclusiveModeEXTPtr
  Result
r <- Ptr Device_T -> SwapchainKHR -> IO Result
vkReleaseFullScreenExclusiveModeEXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) (SwapchainKHR
swapchain)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))


-- | VkSurfaceFullScreenExclusiveInfoEXT - Structure specifying the preferred
-- full-screen transition behavior
--
-- = Description
--
-- If this structure is not present, @fullScreenExclusive@ is considered to
-- be 'FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'FullScreenExclusiveEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data SurfaceFullScreenExclusiveInfoEXT = SurfaceFullScreenExclusiveInfoEXT
  { -- | @fullScreenExclusive@ is a 'FullScreenExclusiveEXT' value specifying the
    -- preferred full-screen transition behavior.
    --
    -- @fullScreenExclusive@ /must/ be a valid 'FullScreenExclusiveEXT' value
    SurfaceFullScreenExclusiveInfoEXT -> FullScreenExclusiveEXT
fullScreenExclusive :: FullScreenExclusiveEXT }
  deriving (Typeable, SurfaceFullScreenExclusiveInfoEXT
-> SurfaceFullScreenExclusiveInfoEXT -> Bool
(SurfaceFullScreenExclusiveInfoEXT
 -> SurfaceFullScreenExclusiveInfoEXT -> Bool)
-> (SurfaceFullScreenExclusiveInfoEXT
    -> SurfaceFullScreenExclusiveInfoEXT -> Bool)
-> Eq SurfaceFullScreenExclusiveInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SurfaceFullScreenExclusiveInfoEXT
-> SurfaceFullScreenExclusiveInfoEXT -> Bool
$c/= :: SurfaceFullScreenExclusiveInfoEXT
-> SurfaceFullScreenExclusiveInfoEXT -> Bool
== :: SurfaceFullScreenExclusiveInfoEXT
-> SurfaceFullScreenExclusiveInfoEXT -> Bool
$c== :: SurfaceFullScreenExclusiveInfoEXT
-> SurfaceFullScreenExclusiveInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SurfaceFullScreenExclusiveInfoEXT)
#endif
deriving instance Show SurfaceFullScreenExclusiveInfoEXT

instance ToCStruct SurfaceFullScreenExclusiveInfoEXT where
  withCStruct :: SurfaceFullScreenExclusiveInfoEXT
-> (Ptr SurfaceFullScreenExclusiveInfoEXT -> IO b) -> IO b
withCStruct x :: SurfaceFullScreenExclusiveInfoEXT
x f :: Ptr SurfaceFullScreenExclusiveInfoEXT -> IO b
f = Int
-> Int -> (Ptr SurfaceFullScreenExclusiveInfoEXT -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr SurfaceFullScreenExclusiveInfoEXT -> IO b) -> IO b)
-> (Ptr SurfaceFullScreenExclusiveInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SurfaceFullScreenExclusiveInfoEXT
p -> Ptr SurfaceFullScreenExclusiveInfoEXT
-> SurfaceFullScreenExclusiveInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SurfaceFullScreenExclusiveInfoEXT
p SurfaceFullScreenExclusiveInfoEXT
x (Ptr SurfaceFullScreenExclusiveInfoEXT -> IO b
f Ptr SurfaceFullScreenExclusiveInfoEXT
p)
  pokeCStruct :: Ptr SurfaceFullScreenExclusiveInfoEXT
-> SurfaceFullScreenExclusiveInfoEXT -> IO b -> IO b
pokeCStruct p :: Ptr SurfaceFullScreenExclusiveInfoEXT
p SurfaceFullScreenExclusiveInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveInfoEXT
p Ptr SurfaceFullScreenExclusiveInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveInfoEXT
p Ptr SurfaceFullScreenExclusiveInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveInfoEXT
p Ptr SurfaceFullScreenExclusiveInfoEXT
-> Int -> Ptr FullScreenExclusiveEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr FullScreenExclusiveEXT)) (FullScreenExclusiveEXT
fullScreenExclusive)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr SurfaceFullScreenExclusiveInfoEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr SurfaceFullScreenExclusiveInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveInfoEXT
p Ptr SurfaceFullScreenExclusiveInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveInfoEXT
p Ptr SurfaceFullScreenExclusiveInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveInfoEXT
p Ptr SurfaceFullScreenExclusiveInfoEXT
-> Int -> Ptr FullScreenExclusiveEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr FullScreenExclusiveEXT)) (FullScreenExclusiveEXT
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct SurfaceFullScreenExclusiveInfoEXT where
  peekCStruct :: Ptr SurfaceFullScreenExclusiveInfoEXT
-> IO SurfaceFullScreenExclusiveInfoEXT
peekCStruct p :: Ptr SurfaceFullScreenExclusiveInfoEXT
p = do
    FullScreenExclusiveEXT
fullScreenExclusive <- Ptr FullScreenExclusiveEXT -> IO FullScreenExclusiveEXT
forall a. Storable a => Ptr a -> IO a
peek @FullScreenExclusiveEXT ((Ptr SurfaceFullScreenExclusiveInfoEXT
p Ptr SurfaceFullScreenExclusiveInfoEXT
-> Int -> Ptr FullScreenExclusiveEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr FullScreenExclusiveEXT))
    SurfaceFullScreenExclusiveInfoEXT
-> IO SurfaceFullScreenExclusiveInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SurfaceFullScreenExclusiveInfoEXT
 -> IO SurfaceFullScreenExclusiveInfoEXT)
-> SurfaceFullScreenExclusiveInfoEXT
-> IO SurfaceFullScreenExclusiveInfoEXT
forall a b. (a -> b) -> a -> b
$ FullScreenExclusiveEXT -> SurfaceFullScreenExclusiveInfoEXT
SurfaceFullScreenExclusiveInfoEXT
             FullScreenExclusiveEXT
fullScreenExclusive

instance Storable SurfaceFullScreenExclusiveInfoEXT where
  sizeOf :: SurfaceFullScreenExclusiveInfoEXT -> Int
sizeOf ~SurfaceFullScreenExclusiveInfoEXT
_ = 24
  alignment :: SurfaceFullScreenExclusiveInfoEXT -> Int
alignment ~SurfaceFullScreenExclusiveInfoEXT
_ = 8
  peek :: Ptr SurfaceFullScreenExclusiveInfoEXT
-> IO SurfaceFullScreenExclusiveInfoEXT
peek = Ptr SurfaceFullScreenExclusiveInfoEXT
-> IO SurfaceFullScreenExclusiveInfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr SurfaceFullScreenExclusiveInfoEXT
-> SurfaceFullScreenExclusiveInfoEXT -> IO ()
poke ptr :: Ptr SurfaceFullScreenExclusiveInfoEXT
ptr poked :: SurfaceFullScreenExclusiveInfoEXT
poked = Ptr SurfaceFullScreenExclusiveInfoEXT
-> SurfaceFullScreenExclusiveInfoEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SurfaceFullScreenExclusiveInfoEXT
ptr SurfaceFullScreenExclusiveInfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero SurfaceFullScreenExclusiveInfoEXT where
  zero :: SurfaceFullScreenExclusiveInfoEXT
zero = FullScreenExclusiveEXT -> SurfaceFullScreenExclusiveInfoEXT
SurfaceFullScreenExclusiveInfoEXT
           FullScreenExclusiveEXT
forall a. Zero a => a
zero


-- | VkSurfaceFullScreenExclusiveWin32InfoEXT - Structure specifying
-- additional creation parameters specific to Win32 fullscreen exclusive
-- mode
--
-- = Description
--
-- Note
--
-- If @hmonitor@ is invalidated (e.g. the monitor is unplugged) during the
-- lifetime of a swapchain created with this structure, operations on that
-- swapchain will return
-- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DATE_KHR'.
--
-- Note
--
-- It is the responsibility of the application to change the display
-- settings of the targeted Win32 display using the appropriate platform
-- APIs. Such changes /may/ alter the surface capabilities reported for the
-- created surface.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data SurfaceFullScreenExclusiveWin32InfoEXT = SurfaceFullScreenExclusiveWin32InfoEXT
  { -- | @hmonitor@ is the Win32 'HMONITOR' handle identifying the display to
    -- create the surface with.
    --
    -- @hmonitor@ /must/ be a valid 'HMONITOR'
    SurfaceFullScreenExclusiveWin32InfoEXT -> Ptr ()
hmonitor :: HMONITOR }
  deriving (Typeable, SurfaceFullScreenExclusiveWin32InfoEXT
-> SurfaceFullScreenExclusiveWin32InfoEXT -> Bool
(SurfaceFullScreenExclusiveWin32InfoEXT
 -> SurfaceFullScreenExclusiveWin32InfoEXT -> Bool)
-> (SurfaceFullScreenExclusiveWin32InfoEXT
    -> SurfaceFullScreenExclusiveWin32InfoEXT -> Bool)
-> Eq SurfaceFullScreenExclusiveWin32InfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SurfaceFullScreenExclusiveWin32InfoEXT
-> SurfaceFullScreenExclusiveWin32InfoEXT -> Bool
$c/= :: SurfaceFullScreenExclusiveWin32InfoEXT
-> SurfaceFullScreenExclusiveWin32InfoEXT -> Bool
== :: SurfaceFullScreenExclusiveWin32InfoEXT
-> SurfaceFullScreenExclusiveWin32InfoEXT -> Bool
$c== :: SurfaceFullScreenExclusiveWin32InfoEXT
-> SurfaceFullScreenExclusiveWin32InfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SurfaceFullScreenExclusiveWin32InfoEXT)
#endif
deriving instance Show SurfaceFullScreenExclusiveWin32InfoEXT

instance ToCStruct SurfaceFullScreenExclusiveWin32InfoEXT where
  withCStruct :: SurfaceFullScreenExclusiveWin32InfoEXT
-> (Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> IO b) -> IO b
withCStruct x :: SurfaceFullScreenExclusiveWin32InfoEXT
x f :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> IO b
f = Int
-> Int
-> (Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> IO b) -> IO b)
-> (Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p -> Ptr SurfaceFullScreenExclusiveWin32InfoEXT
-> SurfaceFullScreenExclusiveWin32InfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p SurfaceFullScreenExclusiveWin32InfoEXT
x (Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> IO b
f Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p)
  pokeCStruct :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT
-> SurfaceFullScreenExclusiveWin32InfoEXT -> IO b -> IO b
pokeCStruct p :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p SurfaceFullScreenExclusiveWin32InfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p Ptr SurfaceFullScreenExclusiveWin32InfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_WIN32_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr HMONITOR)) (Ptr ()
hmonitor)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p Ptr SurfaceFullScreenExclusiveWin32InfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_WIN32_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr HMONITOR)) (Ptr ()
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct SurfaceFullScreenExclusiveWin32InfoEXT where
  peekCStruct :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT
-> IO SurfaceFullScreenExclusiveWin32InfoEXT
peekCStruct p :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p = do
    Ptr ()
hmonitor <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @HMONITOR ((Ptr SurfaceFullScreenExclusiveWin32InfoEXT
p Ptr SurfaceFullScreenExclusiveWin32InfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr HMONITOR))
    SurfaceFullScreenExclusiveWin32InfoEXT
-> IO SurfaceFullScreenExclusiveWin32InfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SurfaceFullScreenExclusiveWin32InfoEXT
 -> IO SurfaceFullScreenExclusiveWin32InfoEXT)
-> SurfaceFullScreenExclusiveWin32InfoEXT
-> IO SurfaceFullScreenExclusiveWin32InfoEXT
forall a b. (a -> b) -> a -> b
$ Ptr () -> SurfaceFullScreenExclusiveWin32InfoEXT
SurfaceFullScreenExclusiveWin32InfoEXT
             Ptr ()
hmonitor

instance Storable SurfaceFullScreenExclusiveWin32InfoEXT where
  sizeOf :: SurfaceFullScreenExclusiveWin32InfoEXT -> Int
sizeOf ~SurfaceFullScreenExclusiveWin32InfoEXT
_ = 24
  alignment :: SurfaceFullScreenExclusiveWin32InfoEXT -> Int
alignment ~SurfaceFullScreenExclusiveWin32InfoEXT
_ = 8
  peek :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT
-> IO SurfaceFullScreenExclusiveWin32InfoEXT
peek = Ptr SurfaceFullScreenExclusiveWin32InfoEXT
-> IO SurfaceFullScreenExclusiveWin32InfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT
-> SurfaceFullScreenExclusiveWin32InfoEXT -> IO ()
poke ptr :: Ptr SurfaceFullScreenExclusiveWin32InfoEXT
ptr poked :: SurfaceFullScreenExclusiveWin32InfoEXT
poked = Ptr SurfaceFullScreenExclusiveWin32InfoEXT
-> SurfaceFullScreenExclusiveWin32InfoEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SurfaceFullScreenExclusiveWin32InfoEXT
ptr SurfaceFullScreenExclusiveWin32InfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero SurfaceFullScreenExclusiveWin32InfoEXT where
  zero :: SurfaceFullScreenExclusiveWin32InfoEXT
zero = Ptr () -> SurfaceFullScreenExclusiveWin32InfoEXT
SurfaceFullScreenExclusiveWin32InfoEXT
           Ptr ()
forall a. Zero a => a
zero


-- | VkSurfaceCapabilitiesFullScreenExclusiveEXT - Structure describing full
-- screen exclusive capabilities of a surface
--
-- = Description
--
-- This structure /can/ be included in the @pNext@ chain of
-- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.SurfaceCapabilities2KHR'
-- to determine support for exclusive full-screen access. If
-- @fullScreenExclusiveSupported@ is
-- 'Vulkan.Core10.FundamentalTypes.FALSE', it indicates that exclusive
-- full-screen access is not obtainable for this surface.
--
-- Applications /must/ not attempt to create swapchains with
-- 'FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT' set if
-- @fullScreenExclusiveSupported@ is
-- 'Vulkan.Core10.FundamentalTypes.FALSE'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data SurfaceCapabilitiesFullScreenExclusiveEXT = SurfaceCapabilitiesFullScreenExclusiveEXT
  { -- No documentation found for Nested "VkSurfaceCapabilitiesFullScreenExclusiveEXT" "fullScreenExclusiveSupported"
    SurfaceCapabilitiesFullScreenExclusiveEXT -> Bool
fullScreenExclusiveSupported :: Bool }
  deriving (Typeable, SurfaceCapabilitiesFullScreenExclusiveEXT
-> SurfaceCapabilitiesFullScreenExclusiveEXT -> Bool
(SurfaceCapabilitiesFullScreenExclusiveEXT
 -> SurfaceCapabilitiesFullScreenExclusiveEXT -> Bool)
-> (SurfaceCapabilitiesFullScreenExclusiveEXT
    -> SurfaceCapabilitiesFullScreenExclusiveEXT -> Bool)
-> Eq SurfaceCapabilitiesFullScreenExclusiveEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SurfaceCapabilitiesFullScreenExclusiveEXT
-> SurfaceCapabilitiesFullScreenExclusiveEXT -> Bool
$c/= :: SurfaceCapabilitiesFullScreenExclusiveEXT
-> SurfaceCapabilitiesFullScreenExclusiveEXT -> Bool
== :: SurfaceCapabilitiesFullScreenExclusiveEXT
-> SurfaceCapabilitiesFullScreenExclusiveEXT -> Bool
$c== :: SurfaceCapabilitiesFullScreenExclusiveEXT
-> SurfaceCapabilitiesFullScreenExclusiveEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SurfaceCapabilitiesFullScreenExclusiveEXT)
#endif
deriving instance Show SurfaceCapabilitiesFullScreenExclusiveEXT

instance ToCStruct SurfaceCapabilitiesFullScreenExclusiveEXT where
  withCStruct :: SurfaceCapabilitiesFullScreenExclusiveEXT
-> (Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> IO b) -> IO b
withCStruct x :: SurfaceCapabilitiesFullScreenExclusiveEXT
x f :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> IO b
f = Int
-> Int
-> (Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> IO b) -> IO b)
-> (Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p -> Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> SurfaceCapabilitiesFullScreenExclusiveEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p SurfaceCapabilitiesFullScreenExclusiveEXT
x (Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> IO b
f Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p)
  pokeCStruct :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> SurfaceCapabilitiesFullScreenExclusiveEXT -> IO b -> IO b
pokeCStruct p :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p SurfaceCapabilitiesFullScreenExclusiveEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_CAPABILITIES_FULL_SCREEN_EXCLUSIVE_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
fullScreenExclusiveSupported))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SURFACE_CAPABILITIES_FULL_SCREEN_EXCLUSIVE_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct SurfaceCapabilitiesFullScreenExclusiveEXT where
  peekCStruct :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> IO SurfaceCapabilitiesFullScreenExclusiveEXT
peekCStruct p :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p = do
    Bool32
fullScreenExclusiveSupported <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
p Ptr SurfaceCapabilitiesFullScreenExclusiveEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    SurfaceCapabilitiesFullScreenExclusiveEXT
-> IO SurfaceCapabilitiesFullScreenExclusiveEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SurfaceCapabilitiesFullScreenExclusiveEXT
 -> IO SurfaceCapabilitiesFullScreenExclusiveEXT)
-> SurfaceCapabilitiesFullScreenExclusiveEXT
-> IO SurfaceCapabilitiesFullScreenExclusiveEXT
forall a b. (a -> b) -> a -> b
$ Bool -> SurfaceCapabilitiesFullScreenExclusiveEXT
SurfaceCapabilitiesFullScreenExclusiveEXT
             (Bool32 -> Bool
bool32ToBool Bool32
fullScreenExclusiveSupported)

instance Storable SurfaceCapabilitiesFullScreenExclusiveEXT where
  sizeOf :: SurfaceCapabilitiesFullScreenExclusiveEXT -> Int
sizeOf ~SurfaceCapabilitiesFullScreenExclusiveEXT
_ = 24
  alignment :: SurfaceCapabilitiesFullScreenExclusiveEXT -> Int
alignment ~SurfaceCapabilitiesFullScreenExclusiveEXT
_ = 8
  peek :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> IO SurfaceCapabilitiesFullScreenExclusiveEXT
peek = Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> IO SurfaceCapabilitiesFullScreenExclusiveEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> SurfaceCapabilitiesFullScreenExclusiveEXT -> IO ()
poke ptr :: Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
ptr poked :: SurfaceCapabilitiesFullScreenExclusiveEXT
poked = Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
-> SurfaceCapabilitiesFullScreenExclusiveEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SurfaceCapabilitiesFullScreenExclusiveEXT
ptr SurfaceCapabilitiesFullScreenExclusiveEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero SurfaceCapabilitiesFullScreenExclusiveEXT where
  zero :: SurfaceCapabilitiesFullScreenExclusiveEXT
zero = Bool -> SurfaceCapabilitiesFullScreenExclusiveEXT
SurfaceCapabilitiesFullScreenExclusiveEXT
           Bool
forall a. Zero a => a
zero


-- | VkFullScreenExclusiveEXT - Hint values an application can specify
-- affecting full-screen transition behavior
--
-- = See Also
--
-- 'SurfaceFullScreenExclusiveInfoEXT'
newtype FullScreenExclusiveEXT = FullScreenExclusiveEXT Int32
  deriving newtype (FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
(FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool)
-> (FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool)
-> Eq FullScreenExclusiveEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
$c/= :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
== :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
$c== :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
Eq, Eq FullScreenExclusiveEXT
Eq FullScreenExclusiveEXT =>
(FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Ordering)
-> (FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool)
-> (FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool)
-> (FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool)
-> (FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool)
-> (FullScreenExclusiveEXT
    -> FullScreenExclusiveEXT -> FullScreenExclusiveEXT)
-> (FullScreenExclusiveEXT
    -> FullScreenExclusiveEXT -> FullScreenExclusiveEXT)
-> Ord FullScreenExclusiveEXT
FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Ordering
FullScreenExclusiveEXT
-> FullScreenExclusiveEXT -> FullScreenExclusiveEXT
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FullScreenExclusiveEXT
-> FullScreenExclusiveEXT -> FullScreenExclusiveEXT
$cmin :: FullScreenExclusiveEXT
-> FullScreenExclusiveEXT -> FullScreenExclusiveEXT
max :: FullScreenExclusiveEXT
-> FullScreenExclusiveEXT -> FullScreenExclusiveEXT
$cmax :: FullScreenExclusiveEXT
-> FullScreenExclusiveEXT -> FullScreenExclusiveEXT
>= :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
$c>= :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
> :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
$c> :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
<= :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
$c<= :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
< :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
$c< :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Bool
compare :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Ordering
$ccompare :: FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> Ordering
$cp1Ord :: Eq FullScreenExclusiveEXT
Ord, Ptr b -> Int -> IO FullScreenExclusiveEXT
Ptr b -> Int -> FullScreenExclusiveEXT -> IO ()
Ptr FullScreenExclusiveEXT -> IO FullScreenExclusiveEXT
Ptr FullScreenExclusiveEXT -> Int -> IO FullScreenExclusiveEXT
Ptr FullScreenExclusiveEXT
-> Int -> FullScreenExclusiveEXT -> IO ()
Ptr FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> IO ()
FullScreenExclusiveEXT -> Int
(FullScreenExclusiveEXT -> Int)
-> (FullScreenExclusiveEXT -> Int)
-> (Ptr FullScreenExclusiveEXT -> Int -> IO FullScreenExclusiveEXT)
-> (Ptr FullScreenExclusiveEXT
    -> Int -> FullScreenExclusiveEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO FullScreenExclusiveEXT)
-> (forall b. Ptr b -> Int -> FullScreenExclusiveEXT -> IO ())
-> (Ptr FullScreenExclusiveEXT -> IO FullScreenExclusiveEXT)
-> (Ptr FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> IO ())
-> Storable FullScreenExclusiveEXT
forall b. Ptr b -> Int -> IO FullScreenExclusiveEXT
forall b. Ptr b -> Int -> FullScreenExclusiveEXT -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> IO ()
$cpoke :: Ptr FullScreenExclusiveEXT -> FullScreenExclusiveEXT -> IO ()
peek :: Ptr FullScreenExclusiveEXT -> IO FullScreenExclusiveEXT
$cpeek :: Ptr FullScreenExclusiveEXT -> IO FullScreenExclusiveEXT
pokeByteOff :: Ptr b -> Int -> FullScreenExclusiveEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> FullScreenExclusiveEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO FullScreenExclusiveEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO FullScreenExclusiveEXT
pokeElemOff :: Ptr FullScreenExclusiveEXT
-> Int -> FullScreenExclusiveEXT -> IO ()
$cpokeElemOff :: Ptr FullScreenExclusiveEXT
-> Int -> FullScreenExclusiveEXT -> IO ()
peekElemOff :: Ptr FullScreenExclusiveEXT -> Int -> IO FullScreenExclusiveEXT
$cpeekElemOff :: Ptr FullScreenExclusiveEXT -> Int -> IO FullScreenExclusiveEXT
alignment :: FullScreenExclusiveEXT -> Int
$calignment :: FullScreenExclusiveEXT -> Int
sizeOf :: FullScreenExclusiveEXT -> Int
$csizeOf :: FullScreenExclusiveEXT -> Int
Storable, FullScreenExclusiveEXT
FullScreenExclusiveEXT -> Zero FullScreenExclusiveEXT
forall a. a -> Zero a
zero :: FullScreenExclusiveEXT
$czero :: FullScreenExclusiveEXT
Zero)

-- | 'FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT' indicates the implementation
-- /should/ determine the appropriate full-screen method by whatever means
-- it deems appropriate.
pattern $bFULL_SCREEN_EXCLUSIVE_DEFAULT_EXT :: FullScreenExclusiveEXT
$mFULL_SCREEN_EXCLUSIVE_DEFAULT_EXT :: forall r.
FullScreenExclusiveEXT -> (Void# -> r) -> (Void# -> r) -> r
FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT = FullScreenExclusiveEXT 0
-- | 'FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT' indicates the implementation /may/
-- use full-screen exclusive mechanisms when available. Such mechanisms
-- /may/ result in better performance and\/or the availability of different
-- presentation capabilities, but /may/ require a more disruptive
-- transition during swapchain initialization, first presentation and\/or
-- destruction.
pattern $bFULL_SCREEN_EXCLUSIVE_ALLOWED_EXT :: FullScreenExclusiveEXT
$mFULL_SCREEN_EXCLUSIVE_ALLOWED_EXT :: forall r.
FullScreenExclusiveEXT -> (Void# -> r) -> (Void# -> r) -> r
FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT = FullScreenExclusiveEXT 1
-- | 'FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT' indicates the implementation
-- /should/ avoid using full-screen mechanisms which rely on disruptive
-- transitions.
pattern $bFULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT :: FullScreenExclusiveEXT
$mFULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT :: forall r.
FullScreenExclusiveEXT -> (Void# -> r) -> (Void# -> r) -> r
FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT = FullScreenExclusiveEXT 2
-- | 'FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT' indicates the
-- application will manage full-screen exclusive mode by using the
-- 'acquireFullScreenExclusiveModeEXT' and
-- 'releaseFullScreenExclusiveModeEXT' commands.
pattern $bFULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT :: FullScreenExclusiveEXT
$mFULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT :: forall r.
FullScreenExclusiveEXT -> (Void# -> r) -> (Void# -> r) -> r
FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT = FullScreenExclusiveEXT 3
{-# complete FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT,
             FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT,
             FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT,
             FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT :: FullScreenExclusiveEXT #-}

instance Show FullScreenExclusiveEXT where
  showsPrec :: Int -> FullScreenExclusiveEXT -> ShowS
showsPrec p :: Int
p = \case
    FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT -> String -> ShowS
showString "FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT"
    FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT -> String -> ShowS
showString "FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT"
    FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT -> String -> ShowS
showString "FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT"
    FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT -> String -> ShowS
showString "FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT"
    FullScreenExclusiveEXT x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "FullScreenExclusiveEXT " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read FullScreenExclusiveEXT where
  readPrec :: ReadPrec FullScreenExclusiveEXT
readPrec = ReadPrec FullScreenExclusiveEXT -> ReadPrec FullScreenExclusiveEXT
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec FullScreenExclusiveEXT)]
-> ReadPrec FullScreenExclusiveEXT
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT", FullScreenExclusiveEXT -> ReadPrec FullScreenExclusiveEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure FullScreenExclusiveEXT
FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT)
                            , ("FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT", FullScreenExclusiveEXT -> ReadPrec FullScreenExclusiveEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure FullScreenExclusiveEXT
FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT)
                            , ("FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT", FullScreenExclusiveEXT -> ReadPrec FullScreenExclusiveEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure FullScreenExclusiveEXT
FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT)
                            , ("FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT", FullScreenExclusiveEXT -> ReadPrec FullScreenExclusiveEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure FullScreenExclusiveEXT
FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT)]
                     ReadPrec FullScreenExclusiveEXT
-> ReadPrec FullScreenExclusiveEXT
-> ReadPrec FullScreenExclusiveEXT
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec FullScreenExclusiveEXT
-> ReadPrec FullScreenExclusiveEXT
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "FullScreenExclusiveEXT")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       FullScreenExclusiveEXT -> ReadPrec FullScreenExclusiveEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> FullScreenExclusiveEXT
FullScreenExclusiveEXT Int32
v)))


type EXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION = 4

-- No documentation found for TopLevel "VK_EXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION"
pattern EXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION :: a
$mEXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION = 4


type EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME = "VK_EXT_full_screen_exclusive"

-- No documentation found for TopLevel "VK_EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME"
pattern EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME :: a
$mEXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME = "VK_EXT_full_screen_exclusive"


type HMONITOR = Ptr ()