{-# language CPP #-}
module Graphics.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
, SurfaceKHR(..)
, SwapchainKHR(..)
, PhysicalDeviceSurfaceInfo2KHR(..)
, PresentModeKHR(..)
, DeviceGroupPresentModeFlagBitsKHR(..)
, DeviceGroupPresentModeFlagsKHR
, HMONITOR
) where
import Control.Exception.Base (bracket)
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 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 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 Graphics.Vulkan.CStruct.Utils (advancePtrBytes)
import Graphics.Vulkan.Core10.BaseType (bool32ToBool)
import Graphics.Vulkan.Core10.BaseType (boolToBool32)
import Graphics.Vulkan.NamedType ((:::))
import Graphics.Vulkan.Core10.BaseType (Bool32)
import Graphics.Vulkan.Core10.Handles (Device)
import Graphics.Vulkan.Core10.Handles (Device(..))
import Graphics.Vulkan.Dynamic (DeviceCmds(pVkAcquireFullScreenExclusiveModeEXT))
import Graphics.Vulkan.Dynamic (DeviceCmds(pVkGetDeviceGroupSurfacePresentModes2EXT))
import Graphics.Vulkan.Dynamic (DeviceCmds(pVkReleaseFullScreenExclusiveModeEXT))
import Graphics.Vulkan.Extensions.VK_KHR_swapchain (DeviceGroupPresentModeFlagBitsKHR(..))
import Graphics.Vulkan.Extensions.VK_KHR_swapchain (DeviceGroupPresentModeFlagsKHR)
import Graphics.Vulkan.Core10.Handles (Device_T)
import Graphics.Vulkan.CStruct (FromCStruct)
import Graphics.Vulkan.CStruct (FromCStruct(..))
import Graphics.Vulkan.Extensions.WSITypes (HMONITOR)
import Graphics.Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceSurfacePresentModes2EXT))
import Graphics.Vulkan.Core10.Handles (PhysicalDevice)
import Graphics.Vulkan.Core10.Handles (PhysicalDevice(..))
import Graphics.Vulkan.Extensions.VK_KHR_get_surface_capabilities2 (PhysicalDeviceSurfaceInfo2KHR)
import Graphics.Vulkan.Core10.Handles (PhysicalDevice_T)
import Graphics.Vulkan.CStruct.Extends (PokeChain)
import Graphics.Vulkan.Extensions.VK_KHR_shared_presentable_image (PresentModeKHR)
import Graphics.Vulkan.Extensions.VK_KHR_shared_presentable_image (PresentModeKHR(..))
import Graphics.Vulkan.Core10.Enums.Result (Result)
import Graphics.Vulkan.Core10.Enums.Result (Result(..))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType)
import Graphics.Vulkan.Extensions.Handles (SwapchainKHR)
import Graphics.Vulkan.Extensions.Handles (SwapchainKHR(..))
import Graphics.Vulkan.CStruct (ToCStruct)
import Graphics.Vulkan.CStruct (ToCStruct(..))
import Graphics.Vulkan.Exception (VulkanException(..))
import Graphics.Vulkan.Zero (Zero)
import Graphics.Vulkan.Zero (Zero(..))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SURFACE_CAPABILITIES_FULL_SCREEN_EXCLUSIVE_EXT))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_INFO_EXT))
import Graphics.Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_WIN32_INFO_EXT))
import Graphics.Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Graphics.Vulkan.Extensions.VK_KHR_swapchain (DeviceGroupPresentModeFlagBitsKHR(..))
import Graphics.Vulkan.Extensions.VK_KHR_swapchain (DeviceGroupPresentModeFlagsKHR)
import Graphics.Vulkan.Extensions.WSITypes (HMONITOR)
import Graphics.Vulkan.Extensions.VK_KHR_get_surface_capabilities2 (PhysicalDeviceSurfaceInfo2KHR(..))
import Graphics.Vulkan.Extensions.VK_KHR_shared_presentable_image (PresentModeKHR(..))
import Graphics.Vulkan.Extensions.Handles (SurfaceKHR(..))
import Graphics.Vulkan.Extensions.Handles (SwapchainKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetPhysicalDeviceSurfacePresentModes2EXT
:: FunPtr (Ptr PhysicalDevice_T -> Ptr (PhysicalDeviceSurfaceInfo2KHR a) -> Ptr Word32 -> Ptr PresentModeKHR -> IO Result) -> Ptr PhysicalDevice_T -> Ptr (PhysicalDeviceSurfaceInfo2KHR a) -> Ptr Word32 -> Ptr PresentModeKHR -> IO Result
getPhysicalDeviceSurfacePresentModes2EXT :: forall a io . (PokeChain a, MonadIO io) => PhysicalDevice -> PhysicalDeviceSurfaceInfo2KHR a -> io (Result, ("presentModes" ::: Vector PresentModeKHR))
getPhysicalDeviceSurfacePresentModes2EXT physicalDevice surfaceInfo = liftIO . evalContT $ do
let vkGetPhysicalDeviceSurfacePresentModes2EXT' = mkVkGetPhysicalDeviceSurfacePresentModes2EXT (pVkGetPhysicalDeviceSurfacePresentModes2EXT (instanceCmds (physicalDevice :: PhysicalDevice)))
let physicalDevice' = physicalDeviceHandle (physicalDevice)
pSurfaceInfo <- ContT $ withCStruct (surfaceInfo)
pPPresentModeCount <- ContT $ bracket (callocBytes @Word32 4) free
r <- lift $ vkGetPhysicalDeviceSurfacePresentModes2EXT' physicalDevice' pSurfaceInfo (pPPresentModeCount) (nullPtr)
lift $ when (r < SUCCESS) (throwIO (VulkanException r))
pPresentModeCount <- lift $ peek @Word32 pPPresentModeCount
pPPresentModes <- ContT $ bracket (callocBytes @PresentModeKHR ((fromIntegral (pPresentModeCount)) * 4)) free
r' <- lift $ vkGetPhysicalDeviceSurfacePresentModes2EXT' physicalDevice' pSurfaceInfo (pPPresentModeCount) (pPPresentModes)
lift $ when (r' < SUCCESS) (throwIO (VulkanException r'))
pPresentModeCount' <- lift $ peek @Word32 pPPresentModeCount
pPresentModes' <- lift $ generateM (fromIntegral (pPresentModeCount')) (\i -> peek @PresentModeKHR ((pPPresentModes `advancePtrBytes` (4 * (i)) :: Ptr PresentModeKHR)))
pure $ ((r'), pPresentModes')
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetDeviceGroupSurfacePresentModes2EXT
:: FunPtr (Ptr Device_T -> Ptr (PhysicalDeviceSurfaceInfo2KHR a) -> Ptr DeviceGroupPresentModeFlagsKHR -> IO Result) -> Ptr Device_T -> Ptr (PhysicalDeviceSurfaceInfo2KHR a) -> Ptr DeviceGroupPresentModeFlagsKHR -> IO Result
getDeviceGroupSurfacePresentModes2EXT :: forall a io . (PokeChain a, MonadIO io) => Device -> PhysicalDeviceSurfaceInfo2KHR a -> io (("modes" ::: DeviceGroupPresentModeFlagsKHR))
getDeviceGroupSurfacePresentModes2EXT device surfaceInfo = liftIO . evalContT $ do
let vkGetDeviceGroupSurfacePresentModes2EXT' = mkVkGetDeviceGroupSurfacePresentModes2EXT (pVkGetDeviceGroupSurfacePresentModes2EXT (deviceCmds (device :: Device)))
pSurfaceInfo <- ContT $ withCStruct (surfaceInfo)
pPModes <- ContT $ bracket (callocBytes @DeviceGroupPresentModeFlagsKHR 4) free
r <- lift $ vkGetDeviceGroupSurfacePresentModes2EXT' (deviceHandle (device)) pSurfaceInfo (pPModes)
lift $ when (r < SUCCESS) (throwIO (VulkanException r))
pModes <- lift $ peek @DeviceGroupPresentModeFlagsKHR pPModes
pure $ (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
acquireFullScreenExclusiveModeEXT :: forall io . MonadIO io => Device -> SwapchainKHR -> io ()
acquireFullScreenExclusiveModeEXT device swapchain = liftIO $ do
let vkAcquireFullScreenExclusiveModeEXT' = mkVkAcquireFullScreenExclusiveModeEXT (pVkAcquireFullScreenExclusiveModeEXT (deviceCmds (device :: Device)))
r <- vkAcquireFullScreenExclusiveModeEXT' (deviceHandle (device)) (swapchain)
when (r < SUCCESS) (throwIO (VulkanException 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
releaseFullScreenExclusiveModeEXT :: forall io . MonadIO io => Device -> SwapchainKHR -> io ()
releaseFullScreenExclusiveModeEXT device swapchain = liftIO $ do
let vkReleaseFullScreenExclusiveModeEXT' = mkVkReleaseFullScreenExclusiveModeEXT (pVkReleaseFullScreenExclusiveModeEXT (deviceCmds (device :: Device)))
r <- vkReleaseFullScreenExclusiveModeEXT' (deviceHandle (device)) (swapchain)
when (r < SUCCESS) (throwIO (VulkanException r))
data SurfaceFullScreenExclusiveInfoEXT = SurfaceFullScreenExclusiveInfoEXT
{
fullScreenExclusive :: FullScreenExclusiveEXT }
deriving (Typeable)
deriving instance Show SurfaceFullScreenExclusiveInfoEXT
instance ToCStruct SurfaceFullScreenExclusiveInfoEXT where
withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
pokeCStruct p SurfaceFullScreenExclusiveInfoEXT{..} f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_INFO_EXT)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr FullScreenExclusiveEXT)) (fullScreenExclusive)
f
cStructSize = 24
cStructAlignment = 8
pokeZeroCStruct p f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_INFO_EXT)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr FullScreenExclusiveEXT)) (zero)
f
instance FromCStruct SurfaceFullScreenExclusiveInfoEXT where
peekCStruct p = do
fullScreenExclusive <- peek @FullScreenExclusiveEXT ((p `plusPtr` 16 :: Ptr FullScreenExclusiveEXT))
pure $ SurfaceFullScreenExclusiveInfoEXT
fullScreenExclusive
instance Storable SurfaceFullScreenExclusiveInfoEXT where
sizeOf ~_ = 24
alignment ~_ = 8
peek = peekCStruct
poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero SurfaceFullScreenExclusiveInfoEXT where
zero = SurfaceFullScreenExclusiveInfoEXT
zero
data SurfaceFullScreenExclusiveWin32InfoEXT = SurfaceFullScreenExclusiveWin32InfoEXT
{
hmonitor :: HMONITOR }
deriving (Typeable)
deriving instance Show SurfaceFullScreenExclusiveWin32InfoEXT
instance ToCStruct SurfaceFullScreenExclusiveWin32InfoEXT where
withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
pokeCStruct p SurfaceFullScreenExclusiveWin32InfoEXT{..} f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_WIN32_INFO_EXT)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr HMONITOR)) (hmonitor)
f
cStructSize = 24
cStructAlignment = 8
pokeZeroCStruct p f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_SURFACE_FULL_SCREEN_EXCLUSIVE_WIN32_INFO_EXT)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr HMONITOR)) (zero)
f
instance FromCStruct SurfaceFullScreenExclusiveWin32InfoEXT where
peekCStruct p = do
hmonitor <- peek @HMONITOR ((p `plusPtr` 16 :: Ptr HMONITOR))
pure $ SurfaceFullScreenExclusiveWin32InfoEXT
hmonitor
instance Storable SurfaceFullScreenExclusiveWin32InfoEXT where
sizeOf ~_ = 24
alignment ~_ = 8
peek = peekCStruct
poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero SurfaceFullScreenExclusiveWin32InfoEXT where
zero = SurfaceFullScreenExclusiveWin32InfoEXT
zero
data SurfaceCapabilitiesFullScreenExclusiveEXT = SurfaceCapabilitiesFullScreenExclusiveEXT
{
fullScreenExclusiveSupported :: Bool }
deriving (Typeable)
deriving instance Show SurfaceCapabilitiesFullScreenExclusiveEXT
instance ToCStruct SurfaceCapabilitiesFullScreenExclusiveEXT where
withCStruct x f = allocaBytesAligned 24 8 $ \p -> pokeCStruct p x (f p)
pokeCStruct p SurfaceCapabilitiesFullScreenExclusiveEXT{..} f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_SURFACE_CAPABILITIES_FULL_SCREEN_EXCLUSIVE_EXT)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (fullScreenExclusiveSupported))
f
cStructSize = 24
cStructAlignment = 8
pokeZeroCStruct p f = do
poke ((p `plusPtr` 0 :: Ptr StructureType)) (STRUCTURE_TYPE_SURFACE_CAPABILITIES_FULL_SCREEN_EXCLUSIVE_EXT)
poke ((p `plusPtr` 8 :: Ptr (Ptr ()))) (nullPtr)
poke ((p `plusPtr` 16 :: Ptr Bool32)) (boolToBool32 (zero))
f
instance FromCStruct SurfaceCapabilitiesFullScreenExclusiveEXT where
peekCStruct p = do
fullScreenExclusiveSupported <- peek @Bool32 ((p `plusPtr` 16 :: Ptr Bool32))
pure $ SurfaceCapabilitiesFullScreenExclusiveEXT
(bool32ToBool fullScreenExclusiveSupported)
instance Storable SurfaceCapabilitiesFullScreenExclusiveEXT where
sizeOf ~_ = 24
alignment ~_ = 8
peek = peekCStruct
poke ptr poked = pokeCStruct ptr poked (pure ())
instance Zero SurfaceCapabilitiesFullScreenExclusiveEXT where
zero = SurfaceCapabilitiesFullScreenExclusiveEXT
zero
newtype FullScreenExclusiveEXT = FullScreenExclusiveEXT Int32
deriving newtype (Eq, Ord, Storable, Zero)
pattern FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT = FullScreenExclusiveEXT 0
pattern FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT = FullScreenExclusiveEXT 1
pattern FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT = FullScreenExclusiveEXT 2
pattern 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 p = \case
FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT -> showString "FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT"
FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT -> showString "FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT"
FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT -> showString "FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT"
FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT -> showString "FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT"
FullScreenExclusiveEXT x -> showParen (p >= 11) (showString "FullScreenExclusiveEXT " . showsPrec 11 x)
instance Read FullScreenExclusiveEXT where
readPrec = parens (choose [("FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT", pure FULL_SCREEN_EXCLUSIVE_DEFAULT_EXT)
, ("FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT", pure FULL_SCREEN_EXCLUSIVE_ALLOWED_EXT)
, ("FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT", pure FULL_SCREEN_EXCLUSIVE_DISALLOWED_EXT)
, ("FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT", pure FULL_SCREEN_EXCLUSIVE_APPLICATION_CONTROLLED_EXT)]
+++
prec 10 (do
expectP (Ident "FullScreenExclusiveEXT")
v <- step readPrec
pure (FullScreenExclusiveEXT v)))
type EXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION = 4
pattern EXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION :: forall a . Integral a => a
pattern EXT_FULL_SCREEN_EXCLUSIVE_SPEC_VERSION = 4
type EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME = "VK_EXT_full_screen_exclusive"
pattern EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern EXT_FULL_SCREEN_EXCLUSIVE_EXTENSION_NAME = "VK_EXT_full_screen_exclusive"