{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_display_control  ( displayPowerControlEXT
                                                 , registerDeviceEventEXT
                                                 , registerDisplayEventEXT
                                                 , getSwapchainCounterEXT
                                                 , DisplayPowerInfoEXT(..)
                                                 , DeviceEventInfoEXT(..)
                                                 , DisplayEventInfoEXT(..)
                                                 , SwapchainCounterCreateInfoEXT(..)
                                                 , DisplayPowerStateEXT( DISPLAY_POWER_STATE_OFF_EXT
                                                                       , DISPLAY_POWER_STATE_SUSPEND_EXT
                                                                       , DISPLAY_POWER_STATE_ON_EXT
                                                                       , ..
                                                                       )
                                                 , DeviceEventTypeEXT( DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT
                                                                     , ..
                                                                     )
                                                 , DisplayEventTypeEXT( DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT
                                                                      , ..
                                                                      )
                                                 , EXT_DISPLAY_CONTROL_SPEC_VERSION
                                                 , pattern EXT_DISPLAY_CONTROL_SPEC_VERSION
                                                 , EXT_DISPLAY_CONTROL_EXTENSION_NAME
                                                 , pattern EXT_DISPLAY_CONTROL_EXTENSION_NAME
                                                 , DisplayKHR(..)
                                                 , SwapchainKHR(..)
                                                 , SurfaceCounterFlagBitsEXT(..)
                                                 , SurfaceCounterFlagsEXT
                                                 ) 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 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 (Word64)
import Text.Read.Lex (Lexeme(Ident))
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkDisplayPowerControlEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetSwapchainCounterEXT))
import Vulkan.Dynamic (DeviceCmds(pVkRegisterDeviceEventEXT))
import Vulkan.Dynamic (DeviceCmds(pVkRegisterDisplayEventEXT))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Extensions.Handles (DisplayKHR)
import Vulkan.Extensions.Handles (DisplayKHR(..))
import Vulkan.Core10.Handles (Fence)
import Vulkan.Core10.Handles (Fence(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.VK_EXT_display_surface_counter (SurfaceCounterFlagBitsEXT)
import Vulkan.Extensions.VK_EXT_display_surface_counter (SurfaceCounterFlagBitsEXT(..))
import Vulkan.Extensions.VK_EXT_display_surface_counter (SurfaceCounterFlagsEXT)
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_DEVICE_EVENT_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DISPLAY_EVENT_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DISPLAY_POWER_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SWAPCHAIN_COUNTER_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.Handles (DisplayKHR(..))
import Vulkan.Extensions.VK_EXT_display_surface_counter (SurfaceCounterFlagBitsEXT(..))
import Vulkan.Extensions.VK_EXT_display_surface_counter (SurfaceCounterFlagsEXT)
import Vulkan.Extensions.Handles (SwapchainKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDisplayPowerControlEXT
  :: FunPtr (Ptr Device_T -> DisplayKHR -> Ptr DisplayPowerInfoEXT -> IO Result) -> Ptr Device_T -> DisplayKHR -> Ptr DisplayPowerInfoEXT -> IO Result

-- | vkDisplayPowerControlEXT - Set the power state of a display
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @display@ /must/ be a valid 'Vulkan.Extensions.Handles.DisplayKHR'
--     handle
--
-- -   @pDisplayPowerInfo@ /must/ be a valid pointer to a valid
--     'DisplayPowerInfoEXT' structure
--
-- -   Both of @device@, and @display@ /must/ have been created, allocated,
--     or retrieved from the same 'Vulkan.Core10.Handles.PhysicalDevice'
--
-- == 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'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Extensions.Handles.DisplayKHR',
-- 'DisplayPowerInfoEXT'
displayPowerControlEXT :: forall io
                        . (MonadIO io)
                       => -- | @device@ is a logical device associated with @display@.
                          Device
                       -> -- | @display@ is the display whose power state is modified.
                          DisplayKHR
                       -> -- | @pDisplayPowerInfo@ is a 'DisplayPowerInfoEXT' structure specifying the
                          -- new power state of @display@.
                          DisplayPowerInfoEXT
                       -> io ()
displayPowerControlEXT :: Device -> DisplayKHR -> DisplayPowerInfoEXT -> io ()
displayPowerControlEXT device :: Device
device display :: DisplayKHR
display displayPowerInfo :: DisplayPowerInfoEXT
displayPowerInfo = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDisplayPowerControlEXTPtr :: FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
   -> IO Result)
vkDisplayPowerControlEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> DisplayKHR
      -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
      -> IO Result)
pVkDisplayPowerControlEXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
   -> IO Result)
vkDisplayPowerControlEXTPtr FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> DisplayKHR
      -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
   -> 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 vkDisplayPowerControlEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDisplayPowerControlEXT' :: Ptr Device_T
-> DisplayKHR
-> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> IO Result
vkDisplayPowerControlEXT' = FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
   -> IO Result)
-> Ptr Device_T
-> DisplayKHR
-> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> IO Result
mkVkDisplayPowerControlEXT FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
   -> IO Result)
vkDisplayPowerControlEXTPtr
  "pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
pDisplayPowerInfo <- ((("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT) -> IO ())
 -> IO ())
-> ContT () IO ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT) -> IO ())
  -> IO ())
 -> ContT () IO ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT))
-> ((("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT) -> IO ())
    -> IO ())
-> ContT () IO ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
forall a b. (a -> b) -> a -> b
$ DisplayPowerInfoEXT
-> (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DisplayPowerInfoEXT
displayPowerInfo)
  Result
r <- IO Result -> ContT () IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT () IO Result)
-> IO Result -> ContT () IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> DisplayKHR
-> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> IO Result
vkDisplayPowerControlEXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DisplayKHR
display) "pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
pDisplayPowerInfo
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () 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))


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkRegisterDeviceEventEXT
  :: FunPtr (Ptr Device_T -> Ptr DeviceEventInfoEXT -> Ptr AllocationCallbacks -> Ptr Fence -> IO Result) -> Ptr Device_T -> Ptr DeviceEventInfoEXT -> Ptr AllocationCallbacks -> Ptr Fence -> IO Result

-- | vkRegisterDeviceEventEXT - Signal a fence when a device event occurs
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pDeviceEventInfo@ /must/ be a valid pointer to a valid
--     'DeviceEventInfoEXT' structure
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pFence@ /must/ be a valid pointer to a
--     'Vulkan.Core10.Handles.Fence' handle
--
-- == 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'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'DeviceEventInfoEXT',
-- 'Vulkan.Core10.Handles.Fence'
registerDeviceEventEXT :: forall io
                        . (MonadIO io)
                       => -- | @device@ is a logical device on which the event /may/ occur.
                          Device
                       -> -- | @pDeviceEventInfo@ is a pointer to a 'DeviceEventInfoEXT' structure
                          -- describing the event of interest to the application.
                          DeviceEventInfoEXT
                       -> -- | @pAllocator@ controls host memory allocation as described in the
                          -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                          -- chapter.
                          ("allocator" ::: Maybe AllocationCallbacks)
                       -> io (Fence)
registerDeviceEventEXT :: Device
-> DeviceEventInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Fence
registerDeviceEventEXT device :: Device
device deviceEventInfo :: DeviceEventInfoEXT
deviceEventInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO Fence -> io Fence
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Fence -> io Fence)
-> (ContT Fence IO Fence -> IO Fence)
-> ContT Fence IO Fence
-> io Fence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Fence IO Fence -> IO Fence
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Fence IO Fence -> io Fence)
-> ContT Fence IO Fence -> io Fence
forall a b. (a -> b) -> a -> b
$ do
  let vkRegisterDeviceEventEXTPtr :: FunPtr
  (Ptr Device_T
   -> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkRegisterDeviceEventEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pFence" ::: Ptr Fence)
      -> IO Result)
pVkRegisterDeviceEventEXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT Fence IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Fence IO ()) -> IO () -> ContT Fence IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkRegisterDeviceEventEXTPtr FunPtr
  (Ptr Device_T
   -> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pFence" ::: Ptr Fence)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> 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 vkRegisterDeviceEventEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkRegisterDeviceEventEXT' :: Ptr Device_T
-> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFence" ::: Ptr Fence)
-> IO Result
vkRegisterDeviceEventEXT' = FunPtr
  (Ptr Device_T
   -> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
-> Ptr Device_T
-> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFence" ::: Ptr Fence)
-> IO Result
mkVkRegisterDeviceEventEXT FunPtr
  (Ptr Device_T
   -> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkRegisterDeviceEventEXTPtr
  "pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
pDeviceEventInfo <- ((("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT) -> IO Fence)
 -> IO Fence)
-> ContT Fence IO ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT) -> IO Fence)
  -> IO Fence)
 -> ContT Fence IO ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT))
-> ((("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT) -> IO Fence)
    -> IO Fence)
-> ContT Fence IO ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
forall a b. (a -> b) -> a -> b
$ DeviceEventInfoEXT
-> (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT) -> IO Fence)
-> IO Fence
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DeviceEventInfoEXT
deviceEventInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
 -> IO Fence)
-> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
  -> IO Fence)
 -> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
    -> IO Fence)
-> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
-> IO Fence
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pFence" ::: Ptr Fence
pPFence <- ((("pFence" ::: Ptr Fence) -> IO Fence) -> IO Fence)
-> ContT Fence IO ("pFence" ::: Ptr Fence)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pFence" ::: Ptr Fence) -> IO Fence) -> IO Fence)
 -> ContT Fence IO ("pFence" ::: Ptr Fence))
-> ((("pFence" ::: Ptr Fence) -> IO Fence) -> IO Fence)
-> ContT Fence IO ("pFence" ::: Ptr Fence)
forall a b. (a -> b) -> a -> b
$ IO ("pFence" ::: Ptr Fence)
-> (("pFence" ::: Ptr Fence) -> IO ())
-> (("pFence" ::: Ptr Fence) -> IO Fence)
-> IO Fence
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pFence" ::: Ptr Fence)
forall a. Int -> IO (Ptr a)
callocBytes @Fence 8) ("pFence" ::: Ptr Fence) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT Fence IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Fence IO Result)
-> IO Result -> ContT Fence IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFence" ::: Ptr Fence)
-> IO Result
vkRegisterDeviceEventEXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
pDeviceEventInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pFence" ::: Ptr Fence
pPFence)
  IO () -> ContT Fence IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Fence IO ()) -> IO () -> ContT Fence 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))
  Fence
pFence <- IO Fence -> ContT Fence IO Fence
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Fence -> ContT Fence IO Fence)
-> IO Fence -> ContT Fence IO Fence
forall a b. (a -> b) -> a -> b
$ ("pFence" ::: Ptr Fence) -> IO Fence
forall a. Storable a => Ptr a -> IO a
peek @Fence "pFence" ::: Ptr Fence
pPFence
  Fence -> ContT Fence IO Fence
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Fence -> ContT Fence IO Fence) -> Fence -> ContT Fence IO Fence
forall a b. (a -> b) -> a -> b
$ (Fence
pFence)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkRegisterDisplayEventEXT
  :: FunPtr (Ptr Device_T -> DisplayKHR -> Ptr DisplayEventInfoEXT -> Ptr AllocationCallbacks -> Ptr Fence -> IO Result) -> Ptr Device_T -> DisplayKHR -> Ptr DisplayEventInfoEXT -> Ptr AllocationCallbacks -> Ptr Fence -> IO Result

-- | vkRegisterDisplayEventEXT - Signal a fence when a display event occurs
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @display@ /must/ be a valid 'Vulkan.Extensions.Handles.DisplayKHR'
--     handle
--
-- -   @pDisplayEventInfo@ /must/ be a valid pointer to a valid
--     'DisplayEventInfoEXT' structure
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pFence@ /must/ be a valid pointer to a
--     'Vulkan.Core10.Handles.Fence' handle
--
-- -   Both of @device@, and @display@ /must/ have been created, allocated,
--     or retrieved from the same 'Vulkan.Core10.Handles.PhysicalDevice'
--
-- == 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'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'DisplayEventInfoEXT',
-- 'Vulkan.Extensions.Handles.DisplayKHR', 'Vulkan.Core10.Handles.Fence'
registerDisplayEventEXT :: forall io
                         . (MonadIO io)
                        => -- | @device@ is a logical device associated with @display@
                           Device
                        -> -- | @display@ is the display on which the event /may/ occur.
                           DisplayKHR
                        -> -- | @pDisplayEventInfo@ is a pointer to a 'DisplayEventInfoEXT' structure
                           -- describing the event of interest to the application.
                           DisplayEventInfoEXT
                        -> -- | @pAllocator@ controls host memory allocation as described in the
                           -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                           -- chapter.
                           ("allocator" ::: Maybe AllocationCallbacks)
                        -> io (Fence)
registerDisplayEventEXT :: Device
-> DisplayKHR
-> DisplayEventInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Fence
registerDisplayEventEXT device :: Device
device display :: DisplayKHR
display displayEventInfo :: DisplayEventInfoEXT
displayEventInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO Fence -> io Fence
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Fence -> io Fence)
-> (ContT Fence IO Fence -> IO Fence)
-> ContT Fence IO Fence
-> io Fence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Fence IO Fence -> IO Fence
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Fence IO Fence -> io Fence)
-> ContT Fence IO Fence -> io Fence
forall a b. (a -> b) -> a -> b
$ do
  let vkRegisterDisplayEventEXTPtr :: FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkRegisterDisplayEventEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> DisplayKHR
      -> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pFence" ::: Ptr Fence)
      -> IO Result)
pVkRegisterDisplayEventEXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT Fence IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Fence IO ()) -> IO () -> ContT Fence IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkRegisterDisplayEventEXTPtr FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> DisplayKHR
      -> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pFence" ::: Ptr Fence)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> 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 vkRegisterDisplayEventEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkRegisterDisplayEventEXT' :: Ptr Device_T
-> DisplayKHR
-> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFence" ::: Ptr Fence)
-> IO Result
vkRegisterDisplayEventEXT' = FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
-> Ptr Device_T
-> DisplayKHR
-> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFence" ::: Ptr Fence)
-> IO Result
mkVkRegisterDisplayEventEXT FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkRegisterDisplayEventEXTPtr
  "pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
pDisplayEventInfo <- ((("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT) -> IO Fence)
 -> IO Fence)
-> ContT Fence IO ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT) -> IO Fence)
  -> IO Fence)
 -> ContT
      Fence IO ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT))
-> ((("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT) -> IO Fence)
    -> IO Fence)
-> ContT Fence IO ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
forall a b. (a -> b) -> a -> b
$ DisplayEventInfoEXT
-> (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT) -> IO Fence)
-> IO Fence
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DisplayEventInfoEXT
displayEventInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
 -> IO Fence)
-> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
  -> IO Fence)
 -> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
    -> IO Fence)
-> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
-> IO Fence
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pFence" ::: Ptr Fence
pPFence <- ((("pFence" ::: Ptr Fence) -> IO Fence) -> IO Fence)
-> ContT Fence IO ("pFence" ::: Ptr Fence)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pFence" ::: Ptr Fence) -> IO Fence) -> IO Fence)
 -> ContT Fence IO ("pFence" ::: Ptr Fence))
-> ((("pFence" ::: Ptr Fence) -> IO Fence) -> IO Fence)
-> ContT Fence IO ("pFence" ::: Ptr Fence)
forall a b. (a -> b) -> a -> b
$ IO ("pFence" ::: Ptr Fence)
-> (("pFence" ::: Ptr Fence) -> IO ())
-> (("pFence" ::: Ptr Fence) -> IO Fence)
-> IO Fence
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pFence" ::: Ptr Fence)
forall a. Int -> IO (Ptr a)
callocBytes @Fence 8) ("pFence" ::: Ptr Fence) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT Fence IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Fence IO Result)
-> IO Result -> ContT Fence IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> DisplayKHR
-> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFence" ::: Ptr Fence)
-> IO Result
vkRegisterDisplayEventEXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DisplayKHR
display) "pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
pDisplayEventInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pFence" ::: Ptr Fence
pPFence)
  IO () -> ContT Fence IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Fence IO ()) -> IO () -> ContT Fence 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))
  Fence
pFence <- IO Fence -> ContT Fence IO Fence
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Fence -> ContT Fence IO Fence)
-> IO Fence -> ContT Fence IO Fence
forall a b. (a -> b) -> a -> b
$ ("pFence" ::: Ptr Fence) -> IO Fence
forall a. Storable a => Ptr a -> IO a
peek @Fence "pFence" ::: Ptr Fence
pPFence
  Fence -> ContT Fence IO Fence
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Fence -> ContT Fence IO Fence) -> Fence -> ContT Fence IO Fence
forall a b. (a -> b) -> a -> b
$ (Fence
pFence)


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

-- | vkGetSwapchainCounterEXT - Query the current value of a surface counter
--
-- = Description
--
-- If a counter is not available because the swapchain is out of date, the
-- implementation /may/ return
-- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DATE_KHR'.
--
-- == Valid Usage
--
-- -   One or more present commands on @swapchain@ /must/ have been
--     processed by the presentation engine
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @swapchain@ /must/ be a valid
--     'Vulkan.Extensions.Handles.SwapchainKHR' handle
--
-- -   @counter@ /must/ be a valid
--     'Vulkan.Extensions.VK_EXT_display_surface_counter.SurfaceCounterFlagBitsEXT'
--     value
--
-- -   @pCounterValue@ /must/ be a valid pointer to a @uint64_t@ value
--
-- -   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_DEVICE_LOST'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DATE_KHR'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Extensions.VK_EXT_display_surface_counter.SurfaceCounterFlagBitsEXT',
-- 'Vulkan.Extensions.Handles.SwapchainKHR'
getSwapchainCounterEXT :: forall io
                        . (MonadIO io)
                       => -- | @device@ is the 'Vulkan.Core10.Handles.Device' associated with
                          -- @swapchain@.
                          Device
                       -> -- | @swapchain@ is the swapchain from which to query the counter value.
                          SwapchainKHR
                       -> -- | @counter@ is the counter to query.
                          SurfaceCounterFlagBitsEXT
                       -> io (("counterValue" ::: Word64))
getSwapchainCounterEXT :: Device
-> SwapchainKHR
-> SurfaceCounterFlagBitsEXT
-> io ("counterValue" ::: Word64)
getSwapchainCounterEXT device :: Device
device swapchain :: SwapchainKHR
swapchain counter :: SurfaceCounterFlagBitsEXT
counter = IO ("counterValue" ::: Word64) -> io ("counterValue" ::: Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("counterValue" ::: Word64) -> io ("counterValue" ::: Word64))
-> (ContT
      ("counterValue" ::: Word64) IO ("counterValue" ::: Word64)
    -> IO ("counterValue" ::: Word64))
-> ContT ("counterValue" ::: Word64) IO ("counterValue" ::: Word64)
-> io ("counterValue" ::: Word64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT ("counterValue" ::: Word64) IO ("counterValue" ::: Word64)
-> IO ("counterValue" ::: Word64)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT ("counterValue" ::: Word64) IO ("counterValue" ::: Word64)
 -> io ("counterValue" ::: Word64))
-> ContT ("counterValue" ::: Word64) IO ("counterValue" ::: Word64)
-> io ("counterValue" ::: Word64)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetSwapchainCounterEXTPtr :: FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> SurfaceCounterFlagBitsEXT
   -> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
   -> IO Result)
vkGetSwapchainCounterEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> SwapchainKHR
      -> SurfaceCounterFlagBitsEXT
      -> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
      -> IO Result)
pVkGetSwapchainCounterEXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT ("counterValue" ::: Word64) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("counterValue" ::: Word64) IO ())
-> IO () -> ContT ("counterValue" ::: Word64) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> SurfaceCounterFlagBitsEXT
   -> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
   -> IO Result)
vkGetSwapchainCounterEXTPtr FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> SurfaceCounterFlagBitsEXT
   -> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> SwapchainKHR
      -> SurfaceCounterFlagBitsEXT
      -> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> SurfaceCounterFlagBitsEXT
   -> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
   -> 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 vkGetSwapchainCounterEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetSwapchainCounterEXT' :: Ptr Device_T
-> SwapchainKHR
-> SurfaceCounterFlagBitsEXT
-> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
-> IO Result
vkGetSwapchainCounterEXT' = FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> SurfaceCounterFlagBitsEXT
   -> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
   -> IO Result)
-> Ptr Device_T
-> SwapchainKHR
-> SurfaceCounterFlagBitsEXT
-> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
-> IO Result
mkVkGetSwapchainCounterEXT FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> SurfaceCounterFlagBitsEXT
   -> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
   -> IO Result)
vkGetSwapchainCounterEXTPtr
  "pCounterValue" ::: Ptr ("counterValue" ::: Word64)
pPCounterValue <- ((("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
  -> IO ("counterValue" ::: Word64))
 -> IO ("counterValue" ::: Word64))
-> ContT
     ("counterValue" ::: Word64)
     IO
     ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
   -> IO ("counterValue" ::: Word64))
  -> IO ("counterValue" ::: Word64))
 -> ContT
      ("counterValue" ::: Word64)
      IO
      ("pCounterValue" ::: Ptr ("counterValue" ::: Word64)))
-> ((("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
     -> IO ("counterValue" ::: Word64))
    -> IO ("counterValue" ::: Word64))
-> ContT
     ("counterValue" ::: Word64)
     IO
     ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
forall a b. (a -> b) -> a -> b
$ IO ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
-> (("pCounterValue" ::: Ptr ("counterValue" ::: Word64)) -> IO ())
-> (("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
    -> IO ("counterValue" ::: Word64))
-> IO ("counterValue" ::: Word64)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
forall a. Int -> IO (Ptr a)
callocBytes @Word64 8) ("pCounterValue" ::: Ptr ("counterValue" ::: Word64)) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT ("counterValue" ::: Word64) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT ("counterValue" ::: Word64) IO Result)
-> IO Result -> ContT ("counterValue" ::: Word64) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> SwapchainKHR
-> SurfaceCounterFlagBitsEXT
-> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
-> IO Result
vkGetSwapchainCounterEXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) (SwapchainKHR
swapchain) (SurfaceCounterFlagBitsEXT
counter) ("pCounterValue" ::: Ptr ("counterValue" ::: Word64)
pPCounterValue)
  IO () -> ContT ("counterValue" ::: Word64) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("counterValue" ::: Word64) IO ())
-> IO () -> ContT ("counterValue" ::: Word64) 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))
  "counterValue" ::: Word64
pCounterValue <- IO ("counterValue" ::: Word64)
-> ContT ("counterValue" ::: Word64) IO ("counterValue" ::: Word64)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("counterValue" ::: Word64)
 -> ContT
      ("counterValue" ::: Word64) IO ("counterValue" ::: Word64))
-> IO ("counterValue" ::: Word64)
-> ContT ("counterValue" ::: Word64) IO ("counterValue" ::: Word64)
forall a b. (a -> b) -> a -> b
$ ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
-> IO ("counterValue" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @Word64 "pCounterValue" ::: Ptr ("counterValue" ::: Word64)
pPCounterValue
  ("counterValue" ::: Word64)
-> ContT ("counterValue" ::: Word64) IO ("counterValue" ::: Word64)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("counterValue" ::: Word64)
 -> ContT
      ("counterValue" ::: Word64) IO ("counterValue" ::: Word64))
-> ("counterValue" ::: Word64)
-> ContT ("counterValue" ::: Word64) IO ("counterValue" ::: Word64)
forall a b. (a -> b) -> a -> b
$ ("counterValue" ::: Word64
pCounterValue)


-- | VkDisplayPowerInfoEXT - Describe the power state of a display
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'DisplayPowerStateEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'displayPowerControlEXT'
data DisplayPowerInfoEXT = DisplayPowerInfoEXT
  { -- | @powerState@ is a 'DisplayPowerStateEXT' value specifying the new power
    -- state of the display.
    --
    -- @powerState@ /must/ be a valid 'DisplayPowerStateEXT' value
    DisplayPowerInfoEXT -> DisplayPowerStateEXT
powerState :: DisplayPowerStateEXT }
  deriving (Typeable, DisplayPowerInfoEXT -> DisplayPowerInfoEXT -> Bool
(DisplayPowerInfoEXT -> DisplayPowerInfoEXT -> Bool)
-> (DisplayPowerInfoEXT -> DisplayPowerInfoEXT -> Bool)
-> Eq DisplayPowerInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayPowerInfoEXT -> DisplayPowerInfoEXT -> Bool
$c/= :: DisplayPowerInfoEXT -> DisplayPowerInfoEXT -> Bool
== :: DisplayPowerInfoEXT -> DisplayPowerInfoEXT -> Bool
$c== :: DisplayPowerInfoEXT -> DisplayPowerInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DisplayPowerInfoEXT)
#endif
deriving instance Show DisplayPowerInfoEXT

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

instance FromCStruct DisplayPowerInfoEXT where
  peekCStruct :: ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> IO DisplayPowerInfoEXT
peekCStruct p :: "pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p = do
    DisplayPowerStateEXT
powerState <- Ptr DisplayPowerStateEXT -> IO DisplayPowerStateEXT
forall a. Storable a => Ptr a -> IO a
peek @DisplayPowerStateEXT (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> Int -> Ptr DisplayPowerStateEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DisplayPowerStateEXT))
    DisplayPowerInfoEXT -> IO DisplayPowerInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DisplayPowerInfoEXT -> IO DisplayPowerInfoEXT)
-> DisplayPowerInfoEXT -> IO DisplayPowerInfoEXT
forall a b. (a -> b) -> a -> b
$ DisplayPowerStateEXT -> DisplayPowerInfoEXT
DisplayPowerInfoEXT
             DisplayPowerStateEXT
powerState

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

instance Zero DisplayPowerInfoEXT where
  zero :: DisplayPowerInfoEXT
zero = DisplayPowerStateEXT -> DisplayPowerInfoEXT
DisplayPowerInfoEXT
           DisplayPowerStateEXT
forall a. Zero a => a
zero


-- | VkDeviceEventInfoEXT - Describe a device event to create
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'DeviceEventTypeEXT', 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'registerDeviceEventEXT'
data DeviceEventInfoEXT = DeviceEventInfoEXT
  { -- | @deviceEvent@ /must/ be a valid 'DeviceEventTypeEXT' value
    DeviceEventInfoEXT -> DeviceEventTypeEXT
deviceEvent :: DeviceEventTypeEXT }
  deriving (Typeable, DeviceEventInfoEXT -> DeviceEventInfoEXT -> Bool
(DeviceEventInfoEXT -> DeviceEventInfoEXT -> Bool)
-> (DeviceEventInfoEXT -> DeviceEventInfoEXT -> Bool)
-> Eq DeviceEventInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceEventInfoEXT -> DeviceEventInfoEXT -> Bool
$c/= :: DeviceEventInfoEXT -> DeviceEventInfoEXT -> Bool
== :: DeviceEventInfoEXT -> DeviceEventInfoEXT -> Bool
$c== :: DeviceEventInfoEXT -> DeviceEventInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceEventInfoEXT)
#endif
deriving instance Show DeviceEventInfoEXT

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

instance FromCStruct DeviceEventInfoEXT where
  peekCStruct :: ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
-> IO DeviceEventInfoEXT
peekCStruct p :: "pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p = do
    DeviceEventTypeEXT
deviceEvent <- Ptr DeviceEventTypeEXT -> IO DeviceEventTypeEXT
forall a. Storable a => Ptr a -> IO a
peek @DeviceEventTypeEXT (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
-> Int -> Ptr DeviceEventTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceEventTypeEXT))
    DeviceEventInfoEXT -> IO DeviceEventInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceEventInfoEXT -> IO DeviceEventInfoEXT)
-> DeviceEventInfoEXT -> IO DeviceEventInfoEXT
forall a b. (a -> b) -> a -> b
$ DeviceEventTypeEXT -> DeviceEventInfoEXT
DeviceEventInfoEXT
             DeviceEventTypeEXT
deviceEvent

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

instance Zero DeviceEventInfoEXT where
  zero :: DeviceEventInfoEXT
zero = DeviceEventTypeEXT -> DeviceEventInfoEXT
DeviceEventInfoEXT
           DeviceEventTypeEXT
forall a. Zero a => a
zero


-- | VkDisplayEventInfoEXT - Describe a display event to create
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'DisplayEventTypeEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'registerDisplayEventEXT'
data DisplayEventInfoEXT = DisplayEventInfoEXT
  { -- | @displayEvent@ is a 'DisplayEventTypeEXT' specifying when the fence will
    -- be signaled.
    --
    -- @displayEvent@ /must/ be a valid 'DisplayEventTypeEXT' value
    DisplayEventInfoEXT -> DisplayEventTypeEXT
displayEvent :: DisplayEventTypeEXT }
  deriving (Typeable, DisplayEventInfoEXT -> DisplayEventInfoEXT -> Bool
(DisplayEventInfoEXT -> DisplayEventInfoEXT -> Bool)
-> (DisplayEventInfoEXT -> DisplayEventInfoEXT -> Bool)
-> Eq DisplayEventInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayEventInfoEXT -> DisplayEventInfoEXT -> Bool
$c/= :: DisplayEventInfoEXT -> DisplayEventInfoEXT -> Bool
== :: DisplayEventInfoEXT -> DisplayEventInfoEXT -> Bool
$c== :: DisplayEventInfoEXT -> DisplayEventInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DisplayEventInfoEXT)
#endif
deriving instance Show DisplayEventInfoEXT

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

instance FromCStruct DisplayEventInfoEXT where
  peekCStruct :: ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
-> IO DisplayEventInfoEXT
peekCStruct p :: "pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p = do
    DisplayEventTypeEXT
displayEvent <- Ptr DisplayEventTypeEXT -> IO DisplayEventTypeEXT
forall a. Storable a => Ptr a -> IO a
peek @DisplayEventTypeEXT (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
-> Int -> Ptr DisplayEventTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DisplayEventTypeEXT))
    DisplayEventInfoEXT -> IO DisplayEventInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DisplayEventInfoEXT -> IO DisplayEventInfoEXT)
-> DisplayEventInfoEXT -> IO DisplayEventInfoEXT
forall a b. (a -> b) -> a -> b
$ DisplayEventTypeEXT -> DisplayEventInfoEXT
DisplayEventInfoEXT
             DisplayEventTypeEXT
displayEvent

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

instance Zero DisplayEventInfoEXT where
  zero :: DisplayEventInfoEXT
zero = DisplayEventTypeEXT -> DisplayEventInfoEXT
DisplayEventInfoEXT
           DisplayEventTypeEXT
forall a. Zero a => a
zero


-- | VkSwapchainCounterCreateInfoEXT - Specify the surface counters desired
--
-- == Valid Usage
--
-- -   The bits in @surfaceCounters@ /must/ be supported by
--     'Vulkan.Extensions.VK_KHR_swapchain.SwapchainCreateInfoKHR'::@surface@,
--     as reported by
--     'Vulkan.Extensions.VK_EXT_display_surface_counter.getPhysicalDeviceSurfaceCapabilities2EXT'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SWAPCHAIN_COUNTER_CREATE_INFO_EXT'
--
-- -   @surfaceCounters@ /must/ be a valid combination of
--     'Vulkan.Extensions.VK_EXT_display_surface_counter.SurfaceCounterFlagBitsEXT'
--     values
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'Vulkan.Extensions.VK_EXT_display_surface_counter.SurfaceCounterFlagsEXT'
data SwapchainCounterCreateInfoEXT = SwapchainCounterCreateInfoEXT
  { -- | @surfaceCounters@ is a bitmask of
    -- 'Vulkan.Extensions.VK_EXT_display_surface_counter.SurfaceCounterFlagBitsEXT'
    -- specifying surface counters to enable for the swapchain.
    SwapchainCounterCreateInfoEXT -> SurfaceCounterFlagBitsEXT
surfaceCounters :: SurfaceCounterFlagsEXT }
  deriving (Typeable, SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> Bool
(SwapchainCounterCreateInfoEXT
 -> SwapchainCounterCreateInfoEXT -> Bool)
-> (SwapchainCounterCreateInfoEXT
    -> SwapchainCounterCreateInfoEXT -> Bool)
-> Eq SwapchainCounterCreateInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> Bool
$c/= :: SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> Bool
== :: SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> Bool
$c== :: SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SwapchainCounterCreateInfoEXT)
#endif
deriving instance Show SwapchainCounterCreateInfoEXT

instance ToCStruct SwapchainCounterCreateInfoEXT where
  withCStruct :: SwapchainCounterCreateInfoEXT
-> (Ptr SwapchainCounterCreateInfoEXT -> IO b) -> IO b
withCStruct x :: SwapchainCounterCreateInfoEXT
x f :: Ptr SwapchainCounterCreateInfoEXT -> IO b
f = Int -> Int -> (Ptr SwapchainCounterCreateInfoEXT -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr SwapchainCounterCreateInfoEXT -> IO b) -> IO b)
-> (Ptr SwapchainCounterCreateInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr SwapchainCounterCreateInfoEXT
p -> Ptr SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SwapchainCounterCreateInfoEXT
p SwapchainCounterCreateInfoEXT
x (Ptr SwapchainCounterCreateInfoEXT -> IO b
f Ptr SwapchainCounterCreateInfoEXT
p)
  pokeCStruct :: Ptr SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> IO b -> IO b
pokeCStruct p :: Ptr SwapchainCounterCreateInfoEXT
p SwapchainCounterCreateInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p Ptr SwapchainCounterCreateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_COUNTER_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p Ptr SwapchainCounterCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr SurfaceCounterFlagBitsEXT -> SurfaceCounterFlagBitsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p Ptr SwapchainCounterCreateInfoEXT
-> Int -> Ptr SurfaceCounterFlagBitsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SurfaceCounterFlagsEXT)) (SurfaceCounterFlagBitsEXT
surfaceCounters)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr SwapchainCounterCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr SwapchainCounterCreateInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p Ptr SwapchainCounterCreateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_COUNTER_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p Ptr SwapchainCounterCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

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

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

instance Zero SwapchainCounterCreateInfoEXT where
  zero :: SwapchainCounterCreateInfoEXT
zero = SurfaceCounterFlagBitsEXT -> SwapchainCounterCreateInfoEXT
SwapchainCounterCreateInfoEXT
           SurfaceCounterFlagBitsEXT
forall a. Zero a => a
zero


-- | VkDisplayPowerStateEXT - Possible power states for a display
--
-- = See Also
--
-- 'DisplayPowerInfoEXT'
newtype DisplayPowerStateEXT = DisplayPowerStateEXT Int32
  deriving newtype (DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
(DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool)
-> (DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool)
-> Eq DisplayPowerStateEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
$c/= :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
== :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
$c== :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
Eq, Eq DisplayPowerStateEXT
Eq DisplayPowerStateEXT =>
(DisplayPowerStateEXT -> DisplayPowerStateEXT -> Ordering)
-> (DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool)
-> (DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool)
-> (DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool)
-> (DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool)
-> (DisplayPowerStateEXT
    -> DisplayPowerStateEXT -> DisplayPowerStateEXT)
-> (DisplayPowerStateEXT
    -> DisplayPowerStateEXT -> DisplayPowerStateEXT)
-> Ord DisplayPowerStateEXT
DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
DisplayPowerStateEXT -> DisplayPowerStateEXT -> Ordering
DisplayPowerStateEXT
-> DisplayPowerStateEXT -> DisplayPowerStateEXT
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 :: DisplayPowerStateEXT
-> DisplayPowerStateEXT -> DisplayPowerStateEXT
$cmin :: DisplayPowerStateEXT
-> DisplayPowerStateEXT -> DisplayPowerStateEXT
max :: DisplayPowerStateEXT
-> DisplayPowerStateEXT -> DisplayPowerStateEXT
$cmax :: DisplayPowerStateEXT
-> DisplayPowerStateEXT -> DisplayPowerStateEXT
>= :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
$c>= :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
> :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
$c> :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
<= :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
$c<= :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
< :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
$c< :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
compare :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Ordering
$ccompare :: DisplayPowerStateEXT -> DisplayPowerStateEXT -> Ordering
$cp1Ord :: Eq DisplayPowerStateEXT
Ord, Ptr b -> Int -> IO DisplayPowerStateEXT
Ptr b -> Int -> DisplayPowerStateEXT -> IO ()
Ptr DisplayPowerStateEXT -> IO DisplayPowerStateEXT
Ptr DisplayPowerStateEXT -> Int -> IO DisplayPowerStateEXT
Ptr DisplayPowerStateEXT -> Int -> DisplayPowerStateEXT -> IO ()
Ptr DisplayPowerStateEXT -> DisplayPowerStateEXT -> IO ()
DisplayPowerStateEXT -> Int
(DisplayPowerStateEXT -> Int)
-> (DisplayPowerStateEXT -> Int)
-> (Ptr DisplayPowerStateEXT -> Int -> IO DisplayPowerStateEXT)
-> (Ptr DisplayPowerStateEXT
    -> Int -> DisplayPowerStateEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DisplayPowerStateEXT)
-> (forall b. Ptr b -> Int -> DisplayPowerStateEXT -> IO ())
-> (Ptr DisplayPowerStateEXT -> IO DisplayPowerStateEXT)
-> (Ptr DisplayPowerStateEXT -> DisplayPowerStateEXT -> IO ())
-> Storable DisplayPowerStateEXT
forall b. Ptr b -> Int -> IO DisplayPowerStateEXT
forall b. Ptr b -> Int -> DisplayPowerStateEXT -> 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 DisplayPowerStateEXT -> DisplayPowerStateEXT -> IO ()
$cpoke :: Ptr DisplayPowerStateEXT -> DisplayPowerStateEXT -> IO ()
peek :: Ptr DisplayPowerStateEXT -> IO DisplayPowerStateEXT
$cpeek :: Ptr DisplayPowerStateEXT -> IO DisplayPowerStateEXT
pokeByteOff :: Ptr b -> Int -> DisplayPowerStateEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayPowerStateEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO DisplayPowerStateEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DisplayPowerStateEXT
pokeElemOff :: Ptr DisplayPowerStateEXT -> Int -> DisplayPowerStateEXT -> IO ()
$cpokeElemOff :: Ptr DisplayPowerStateEXT -> Int -> DisplayPowerStateEXT -> IO ()
peekElemOff :: Ptr DisplayPowerStateEXT -> Int -> IO DisplayPowerStateEXT
$cpeekElemOff :: Ptr DisplayPowerStateEXT -> Int -> IO DisplayPowerStateEXT
alignment :: DisplayPowerStateEXT -> Int
$calignment :: DisplayPowerStateEXT -> Int
sizeOf :: DisplayPowerStateEXT -> Int
$csizeOf :: DisplayPowerStateEXT -> Int
Storable, DisplayPowerStateEXT
DisplayPowerStateEXT -> Zero DisplayPowerStateEXT
forall a. a -> Zero a
zero :: DisplayPowerStateEXT
$czero :: DisplayPowerStateEXT
Zero)

-- | 'DISPLAY_POWER_STATE_OFF_EXT' specifies that the display is powered
-- down.
pattern $bDISPLAY_POWER_STATE_OFF_EXT :: DisplayPowerStateEXT
$mDISPLAY_POWER_STATE_OFF_EXT :: forall r. DisplayPowerStateEXT -> (Void# -> r) -> (Void# -> r) -> r
DISPLAY_POWER_STATE_OFF_EXT = DisplayPowerStateEXT 0
-- | 'DISPLAY_POWER_STATE_SUSPEND_EXT' specifies that the display is put into
-- a low power mode, from which it /may/ be able to transition back to
-- 'DISPLAY_POWER_STATE_ON_EXT' more quickly than if it were in
-- 'DISPLAY_POWER_STATE_OFF_EXT'. This state /may/ be the same as
-- 'DISPLAY_POWER_STATE_OFF_EXT'.
pattern $bDISPLAY_POWER_STATE_SUSPEND_EXT :: DisplayPowerStateEXT
$mDISPLAY_POWER_STATE_SUSPEND_EXT :: forall r. DisplayPowerStateEXT -> (Void# -> r) -> (Void# -> r) -> r
DISPLAY_POWER_STATE_SUSPEND_EXT = DisplayPowerStateEXT 1
-- | 'DISPLAY_POWER_STATE_ON_EXT' specifies that the display is powered on.
pattern $bDISPLAY_POWER_STATE_ON_EXT :: DisplayPowerStateEXT
$mDISPLAY_POWER_STATE_ON_EXT :: forall r. DisplayPowerStateEXT -> (Void# -> r) -> (Void# -> r) -> r
DISPLAY_POWER_STATE_ON_EXT = DisplayPowerStateEXT 2
{-# complete DISPLAY_POWER_STATE_OFF_EXT,
             DISPLAY_POWER_STATE_SUSPEND_EXT,
             DISPLAY_POWER_STATE_ON_EXT :: DisplayPowerStateEXT #-}

instance Show DisplayPowerStateEXT where
  showsPrec :: Int -> DisplayPowerStateEXT -> ShowS
showsPrec p :: Int
p = \case
    DISPLAY_POWER_STATE_OFF_EXT -> String -> ShowS
showString "DISPLAY_POWER_STATE_OFF_EXT"
    DISPLAY_POWER_STATE_SUSPEND_EXT -> String -> ShowS
showString "DISPLAY_POWER_STATE_SUSPEND_EXT"
    DISPLAY_POWER_STATE_ON_EXT -> String -> ShowS
showString "DISPLAY_POWER_STATE_ON_EXT"
    DisplayPowerStateEXT x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DisplayPowerStateEXT " 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 DisplayPowerStateEXT where
  readPrec :: ReadPrec DisplayPowerStateEXT
readPrec = ReadPrec DisplayPowerStateEXT -> ReadPrec DisplayPowerStateEXT
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec DisplayPowerStateEXT)]
-> ReadPrec DisplayPowerStateEXT
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("DISPLAY_POWER_STATE_OFF_EXT", DisplayPowerStateEXT -> ReadPrec DisplayPowerStateEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure DisplayPowerStateEXT
DISPLAY_POWER_STATE_OFF_EXT)
                            , ("DISPLAY_POWER_STATE_SUSPEND_EXT", DisplayPowerStateEXT -> ReadPrec DisplayPowerStateEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure DisplayPowerStateEXT
DISPLAY_POWER_STATE_SUSPEND_EXT)
                            , ("DISPLAY_POWER_STATE_ON_EXT", DisplayPowerStateEXT -> ReadPrec DisplayPowerStateEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure DisplayPowerStateEXT
DISPLAY_POWER_STATE_ON_EXT)]
                     ReadPrec DisplayPowerStateEXT
-> ReadPrec DisplayPowerStateEXT -> ReadPrec DisplayPowerStateEXT
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec DisplayPowerStateEXT -> ReadPrec DisplayPowerStateEXT
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "DisplayPowerStateEXT")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       DisplayPowerStateEXT -> ReadPrec DisplayPowerStateEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> DisplayPowerStateEXT
DisplayPowerStateEXT Int32
v)))


-- | VkDeviceEventTypeEXT - Events that can occur on a device object
--
-- = See Also
--
-- 'DeviceEventInfoEXT'
newtype DeviceEventTypeEXT = DeviceEventTypeEXT Int32
  deriving newtype (DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
(DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool)
-> (DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool)
-> Eq DeviceEventTypeEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
$c/= :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
== :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
$c== :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
Eq, Eq DeviceEventTypeEXT
Eq DeviceEventTypeEXT =>
(DeviceEventTypeEXT -> DeviceEventTypeEXT -> Ordering)
-> (DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool)
-> (DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool)
-> (DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool)
-> (DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool)
-> (DeviceEventTypeEXT -> DeviceEventTypeEXT -> DeviceEventTypeEXT)
-> (DeviceEventTypeEXT -> DeviceEventTypeEXT -> DeviceEventTypeEXT)
-> Ord DeviceEventTypeEXT
DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
DeviceEventTypeEXT -> DeviceEventTypeEXT -> Ordering
DeviceEventTypeEXT -> DeviceEventTypeEXT -> DeviceEventTypeEXT
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 :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> DeviceEventTypeEXT
$cmin :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> DeviceEventTypeEXT
max :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> DeviceEventTypeEXT
$cmax :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> DeviceEventTypeEXT
>= :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
$c>= :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
> :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
$c> :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
<= :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
$c<= :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
< :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
$c< :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
compare :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Ordering
$ccompare :: DeviceEventTypeEXT -> DeviceEventTypeEXT -> Ordering
$cp1Ord :: Eq DeviceEventTypeEXT
Ord, Ptr b -> Int -> IO DeviceEventTypeEXT
Ptr b -> Int -> DeviceEventTypeEXT -> IO ()
Ptr DeviceEventTypeEXT -> IO DeviceEventTypeEXT
Ptr DeviceEventTypeEXT -> Int -> IO DeviceEventTypeEXT
Ptr DeviceEventTypeEXT -> Int -> DeviceEventTypeEXT -> IO ()
Ptr DeviceEventTypeEXT -> DeviceEventTypeEXT -> IO ()
DeviceEventTypeEXT -> Int
(DeviceEventTypeEXT -> Int)
-> (DeviceEventTypeEXT -> Int)
-> (Ptr DeviceEventTypeEXT -> Int -> IO DeviceEventTypeEXT)
-> (Ptr DeviceEventTypeEXT -> Int -> DeviceEventTypeEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DeviceEventTypeEXT)
-> (forall b. Ptr b -> Int -> DeviceEventTypeEXT -> IO ())
-> (Ptr DeviceEventTypeEXT -> IO DeviceEventTypeEXT)
-> (Ptr DeviceEventTypeEXT -> DeviceEventTypeEXT -> IO ())
-> Storable DeviceEventTypeEXT
forall b. Ptr b -> Int -> IO DeviceEventTypeEXT
forall b. Ptr b -> Int -> DeviceEventTypeEXT -> 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 DeviceEventTypeEXT -> DeviceEventTypeEXT -> IO ()
$cpoke :: Ptr DeviceEventTypeEXT -> DeviceEventTypeEXT -> IO ()
peek :: Ptr DeviceEventTypeEXT -> IO DeviceEventTypeEXT
$cpeek :: Ptr DeviceEventTypeEXT -> IO DeviceEventTypeEXT
pokeByteOff :: Ptr b -> Int -> DeviceEventTypeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DeviceEventTypeEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO DeviceEventTypeEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DeviceEventTypeEXT
pokeElemOff :: Ptr DeviceEventTypeEXT -> Int -> DeviceEventTypeEXT -> IO ()
$cpokeElemOff :: Ptr DeviceEventTypeEXT -> Int -> DeviceEventTypeEXT -> IO ()
peekElemOff :: Ptr DeviceEventTypeEXT -> Int -> IO DeviceEventTypeEXT
$cpeekElemOff :: Ptr DeviceEventTypeEXT -> Int -> IO DeviceEventTypeEXT
alignment :: DeviceEventTypeEXT -> Int
$calignment :: DeviceEventTypeEXT -> Int
sizeOf :: DeviceEventTypeEXT -> Int
$csizeOf :: DeviceEventTypeEXT -> Int
Storable, DeviceEventTypeEXT
DeviceEventTypeEXT -> Zero DeviceEventTypeEXT
forall a. a -> Zero a
zero :: DeviceEventTypeEXT
$czero :: DeviceEventTypeEXT
Zero)

-- | 'DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT' specifies that the fence is
-- signaled when a display is plugged into or unplugged from the specified
-- device. Applications /can/ use this notification to determine when they
-- need to re-enumerate the available displays on a device.
pattern $bDEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT :: DeviceEventTypeEXT
$mDEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT :: forall r. DeviceEventTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT = DeviceEventTypeEXT 0
{-# complete DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT :: DeviceEventTypeEXT #-}

instance Show DeviceEventTypeEXT where
  showsPrec :: Int -> DeviceEventTypeEXT -> ShowS
showsPrec p :: Int
p = \case
    DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT -> String -> ShowS
showString "DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT"
    DeviceEventTypeEXT x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DeviceEventTypeEXT " 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 DeviceEventTypeEXT where
  readPrec :: ReadPrec DeviceEventTypeEXT
readPrec = ReadPrec DeviceEventTypeEXT -> ReadPrec DeviceEventTypeEXT
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec DeviceEventTypeEXT)]
-> ReadPrec DeviceEventTypeEXT
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT", DeviceEventTypeEXT -> ReadPrec DeviceEventTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure DeviceEventTypeEXT
DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT)]
                     ReadPrec DeviceEventTypeEXT
-> ReadPrec DeviceEventTypeEXT -> ReadPrec DeviceEventTypeEXT
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec DeviceEventTypeEXT -> ReadPrec DeviceEventTypeEXT
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "DeviceEventTypeEXT")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       DeviceEventTypeEXT -> ReadPrec DeviceEventTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> DeviceEventTypeEXT
DeviceEventTypeEXT Int32
v)))


-- | VkDisplayEventTypeEXT - Events that can occur on a display object
--
-- = See Also
--
-- 'DisplayEventInfoEXT'
newtype DisplayEventTypeEXT = DisplayEventTypeEXT Int32
  deriving newtype (DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
(DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool)
-> (DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool)
-> Eq DisplayEventTypeEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
$c/= :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
== :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
$c== :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
Eq, Eq DisplayEventTypeEXT
Eq DisplayEventTypeEXT =>
(DisplayEventTypeEXT -> DisplayEventTypeEXT -> Ordering)
-> (DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool)
-> (DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool)
-> (DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool)
-> (DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool)
-> (DisplayEventTypeEXT
    -> DisplayEventTypeEXT -> DisplayEventTypeEXT)
-> (DisplayEventTypeEXT
    -> DisplayEventTypeEXT -> DisplayEventTypeEXT)
-> Ord DisplayEventTypeEXT
DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
DisplayEventTypeEXT -> DisplayEventTypeEXT -> Ordering
DisplayEventTypeEXT -> DisplayEventTypeEXT -> DisplayEventTypeEXT
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 :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> DisplayEventTypeEXT
$cmin :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> DisplayEventTypeEXT
max :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> DisplayEventTypeEXT
$cmax :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> DisplayEventTypeEXT
>= :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
$c>= :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
> :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
$c> :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
<= :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
$c<= :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
< :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
$c< :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
compare :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Ordering
$ccompare :: DisplayEventTypeEXT -> DisplayEventTypeEXT -> Ordering
$cp1Ord :: Eq DisplayEventTypeEXT
Ord, Ptr b -> Int -> IO DisplayEventTypeEXT
Ptr b -> Int -> DisplayEventTypeEXT -> IO ()
Ptr DisplayEventTypeEXT -> IO DisplayEventTypeEXT
Ptr DisplayEventTypeEXT -> Int -> IO DisplayEventTypeEXT
Ptr DisplayEventTypeEXT -> Int -> DisplayEventTypeEXT -> IO ()
Ptr DisplayEventTypeEXT -> DisplayEventTypeEXT -> IO ()
DisplayEventTypeEXT -> Int
(DisplayEventTypeEXT -> Int)
-> (DisplayEventTypeEXT -> Int)
-> (Ptr DisplayEventTypeEXT -> Int -> IO DisplayEventTypeEXT)
-> (Ptr DisplayEventTypeEXT -> Int -> DisplayEventTypeEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DisplayEventTypeEXT)
-> (forall b. Ptr b -> Int -> DisplayEventTypeEXT -> IO ())
-> (Ptr DisplayEventTypeEXT -> IO DisplayEventTypeEXT)
-> (Ptr DisplayEventTypeEXT -> DisplayEventTypeEXT -> IO ())
-> Storable DisplayEventTypeEXT
forall b. Ptr b -> Int -> IO DisplayEventTypeEXT
forall b. Ptr b -> Int -> DisplayEventTypeEXT -> 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 DisplayEventTypeEXT -> DisplayEventTypeEXT -> IO ()
$cpoke :: Ptr DisplayEventTypeEXT -> DisplayEventTypeEXT -> IO ()
peek :: Ptr DisplayEventTypeEXT -> IO DisplayEventTypeEXT
$cpeek :: Ptr DisplayEventTypeEXT -> IO DisplayEventTypeEXT
pokeByteOff :: Ptr b -> Int -> DisplayEventTypeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayEventTypeEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO DisplayEventTypeEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DisplayEventTypeEXT
pokeElemOff :: Ptr DisplayEventTypeEXT -> Int -> DisplayEventTypeEXT -> IO ()
$cpokeElemOff :: Ptr DisplayEventTypeEXT -> Int -> DisplayEventTypeEXT -> IO ()
peekElemOff :: Ptr DisplayEventTypeEXT -> Int -> IO DisplayEventTypeEXT
$cpeekElemOff :: Ptr DisplayEventTypeEXT -> Int -> IO DisplayEventTypeEXT
alignment :: DisplayEventTypeEXT -> Int
$calignment :: DisplayEventTypeEXT -> Int
sizeOf :: DisplayEventTypeEXT -> Int
$csizeOf :: DisplayEventTypeEXT -> Int
Storable, DisplayEventTypeEXT
DisplayEventTypeEXT -> Zero DisplayEventTypeEXT
forall a. a -> Zero a
zero :: DisplayEventTypeEXT
$czero :: DisplayEventTypeEXT
Zero)

-- | 'DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT' specifies that the fence is
-- signaled when the first pixel of the next display refresh cycle leaves
-- the display engine for the display.
pattern $bDISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT :: DisplayEventTypeEXT
$mDISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT :: forall r. DisplayEventTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT = DisplayEventTypeEXT 0
{-# complete DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT :: DisplayEventTypeEXT #-}

instance Show DisplayEventTypeEXT where
  showsPrec :: Int -> DisplayEventTypeEXT -> ShowS
showsPrec p :: Int
p = \case
    DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT -> String -> ShowS
showString "DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT"
    DisplayEventTypeEXT x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DisplayEventTypeEXT " 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 DisplayEventTypeEXT where
  readPrec :: ReadPrec DisplayEventTypeEXT
readPrec = ReadPrec DisplayEventTypeEXT -> ReadPrec DisplayEventTypeEXT
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec DisplayEventTypeEXT)]
-> ReadPrec DisplayEventTypeEXT
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT", DisplayEventTypeEXT -> ReadPrec DisplayEventTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure DisplayEventTypeEXT
DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT)]
                     ReadPrec DisplayEventTypeEXT
-> ReadPrec DisplayEventTypeEXT -> ReadPrec DisplayEventTypeEXT
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec DisplayEventTypeEXT -> ReadPrec DisplayEventTypeEXT
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "DisplayEventTypeEXT")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       DisplayEventTypeEXT -> ReadPrec DisplayEventTypeEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> DisplayEventTypeEXT
DisplayEventTypeEXT Int32
v)))


type EXT_DISPLAY_CONTROL_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_DISPLAY_CONTROL_SPEC_VERSION"
pattern EXT_DISPLAY_CONTROL_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DISPLAY_CONTROL_SPEC_VERSION :: a
$mEXT_DISPLAY_CONTROL_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_DISPLAY_CONTROL_SPEC_VERSION = 1


type EXT_DISPLAY_CONTROL_EXTENSION_NAME = "VK_EXT_display_control"

-- No documentation found for TopLevel "VK_EXT_DISPLAY_CONTROL_EXTENSION_NAME"
pattern EXT_DISPLAY_CONTROL_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DISPLAY_CONTROL_EXTENSION_NAME :: a
$mEXT_DISPLAY_CONTROL_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_DISPLAY_CONTROL_EXTENSION_NAME = "VK_EXT_display_control"