{-# 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 Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showsPrec)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
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 GHC.Show (Show(showsPrec))
import Data.Word (Word64)
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.Core10.Handles (Device(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.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.Exception (VulkanException(..))
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
displayPowerControlEXT :: forall io
                        . (MonadIO io)
                       => 
                          Device
                       -> 
                          DisplayKHR
                       -> 
                          
                          DisplayPowerInfoEXT
                       -> io ()
displayPowerControlEXT :: forall (io :: * -> *).
MonadIO io =>
Device -> DisplayKHR -> DisplayPowerInfoEXT -> io ()
displayPowerControlEXT Device
device DisplayKHR
display DisplayPowerInfoEXT
displayPowerInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkDisplayPowerControlEXTPtr :: FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
   -> IO Result)
vkDisplayPowerControlEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> DisplayKHR
      -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
      -> IO Result)
pVkDisplayPowerControlEXT (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
   -> IO Result)
vkDisplayPowerControlEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkDisplayPowerControlEXT is null" forall a. Maybe a
Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DisplayPowerInfoEXT
displayPowerInfo)
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDisplayPowerControlEXT" (Ptr Device_T
-> DisplayKHR
-> ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> IO Result
vkDisplayPowerControlEXT'
                                                             (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                             (DisplayKHR
display)
                                                             "pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
pDisplayPowerInfo)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
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
registerDeviceEventEXT :: forall io
                        . (MonadIO io)
                       => 
                          Device
                       -> 
                          
                          DeviceEventInfoEXT
                       -> 
                          
                          
                          ("allocator" ::: Maybe AllocationCallbacks)
                       -> io (Fence)
registerDeviceEventEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> DeviceEventInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Fence
registerDeviceEventEXT Device
device
                         DeviceEventInfoEXT
deviceEventInfo
                         "allocator" ::: Maybe AllocationCallbacks
allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let 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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkRegisterDeviceEventEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkRegisterDeviceEventEXT is null" forall a. Maybe a
Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DeviceEventInfoEXT
deviceEventInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pFence" ::: Ptr Fence
pPFence <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Fence Int
8) forall a. Ptr a -> IO ()
free
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkRegisterDeviceEventEXT" (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))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Fence
pFence <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Fence "pFence" ::: Ptr Fence
pPFence
  forall (f :: * -> *) a. Applicative f => a -> f a
pure 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
registerDisplayEventEXT :: forall io
                         . (MonadIO io)
                        => 
                           Device
                        -> 
                           DisplayKHR
                        -> 
                           
                           DisplayEventInfoEXT
                        -> 
                           
                           
                           ("allocator" ::: Maybe AllocationCallbacks)
                        -> io (Fence)
registerDisplayEventEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> DisplayKHR
-> DisplayEventInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Fence
registerDisplayEventEXT Device
device
                          DisplayKHR
display
                          DisplayEventInfoEXT
displayEventInfo
                          "allocator" ::: Maybe AllocationCallbacks
allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let 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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DisplayKHR
   -> ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkRegisterDisplayEventEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkRegisterDisplayEventEXT is null" forall a. Maybe a
Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DisplayEventInfoEXT
displayEventInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pFence" ::: Ptr Fence
pPFence <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Fence Int
8) forall a. Ptr a -> IO ()
free
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkRegisterDisplayEventEXT" (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))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Fence
pFence <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Fence "pFence" ::: Ptr Fence
pPFence
  forall (f :: * -> *) a. Applicative f => a -> f a
pure 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
getSwapchainCounterEXT :: forall io
                        . (MonadIO io)
                       => 
                          
                          Device
                       -> 
                          SwapchainKHR
                       -> 
                          
                          
                          SurfaceCounterFlagBitsEXT
                       -> io (("counterValue" ::: Word64))
getSwapchainCounterEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> SwapchainKHR
-> SurfaceCounterFlagBitsEXT
-> io ("counterValue" ::: Word64)
getSwapchainCounterEXT Device
device SwapchainKHR
swapchain SurfaceCounterFlagBitsEXT
counter = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let 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 (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> SwapchainKHR
   -> SurfaceCounterFlagBitsEXT
   -> ("pCounterValue" ::: Ptr ("counterValue" ::: Word64))
   -> IO Result)
vkGetSwapchainCounterEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetSwapchainCounterEXT is null" forall a. Maybe a
Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Word64 Int
8) forall a. Ptr a -> IO ()
free
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetSwapchainCounterEXT" (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))
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  "counterValue" ::: Word64
pCounterValue <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word64 "pCounterValue" ::: Ptr ("counterValue" ::: Word64)
pPCounterValue
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("counterValue" ::: Word64
pCounterValue)
data DisplayPowerInfoEXT = DisplayPowerInfoEXT
  { 
    
    
    
    
    DisplayPowerInfoEXT -> DisplayPowerStateEXT
powerState :: DisplayPowerStateEXT }
  deriving (Typeable, DisplayPowerInfoEXT -> DisplayPowerInfoEXT -> Bool
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 :: forall b.
DisplayPowerInfoEXT
-> (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT) -> IO b)
-> IO b
withCStruct DisplayPowerInfoEXT
x ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p -> 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 :: forall b.
("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> DisplayPowerInfoEXT -> IO b -> IO b
pokeCStruct "pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p DisplayPowerInfoEXT{DisplayPowerStateEXT
powerState :: DisplayPowerStateEXT
$sel:powerState:DisplayPowerInfoEXT :: DisplayPowerInfoEXT -> DisplayPowerStateEXT
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DISPLAY_POWER_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DisplayPowerStateEXT)) (DisplayPowerStateEXT
powerState)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DISPLAY_POWER_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DisplayPowerStateEXT)) (forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct DisplayPowerInfoEXT where
  peekCStruct :: ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> IO DisplayPowerInfoEXT
peekCStruct "pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p = do
    DisplayPowerStateEXT
powerState <- forall a. Storable a => Ptr a -> IO a
peek @DisplayPowerStateEXT (("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DisplayPowerStateEXT))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DisplayPowerStateEXT -> DisplayPowerInfoEXT
DisplayPowerInfoEXT
             DisplayPowerStateEXT
powerState
instance Storable DisplayPowerInfoEXT where
  sizeOf :: DisplayPowerInfoEXT -> Int
sizeOf ~DisplayPowerInfoEXT
_ = Int
24
  alignment :: DisplayPowerInfoEXT -> Int
alignment ~DisplayPowerInfoEXT
_ = Int
8
  peek :: ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> IO DisplayPowerInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT)
-> DisplayPowerInfoEXT -> IO ()
poke "pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
ptr DisplayPowerInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pDisplayPowerInfo" ::: Ptr DisplayPowerInfoEXT
ptr DisplayPowerInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DisplayPowerInfoEXT where
  zero :: DisplayPowerInfoEXT
zero = DisplayPowerStateEXT -> DisplayPowerInfoEXT
DisplayPowerInfoEXT
           forall a. Zero a => a
zero
data DeviceEventInfoEXT = DeviceEventInfoEXT
  { 
    
    DeviceEventInfoEXT -> DeviceEventTypeEXT
deviceEvent :: DeviceEventTypeEXT }
  deriving (Typeable, DeviceEventInfoEXT -> DeviceEventInfoEXT -> Bool
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 :: forall b.
DeviceEventInfoEXT
-> (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT) -> IO b)
-> IO b
withCStruct DeviceEventInfoEXT
x ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p -> 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 :: forall b.
("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
-> DeviceEventInfoEXT -> IO b -> IO b
pokeCStruct "pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p DeviceEventInfoEXT{DeviceEventTypeEXT
deviceEvent :: DeviceEventTypeEXT
$sel:deviceEvent:DeviceEventInfoEXT :: DeviceEventInfoEXT -> DeviceEventTypeEXT
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_EVENT_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceEventTypeEXT)) (DeviceEventTypeEXT
deviceEvent)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_EVENT_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceEventTypeEXT)) (forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct DeviceEventInfoEXT where
  peekCStruct :: ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
-> IO DeviceEventInfoEXT
peekCStruct "pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p = do
    DeviceEventTypeEXT
deviceEvent <- forall a. Storable a => Ptr a -> IO a
peek @DeviceEventTypeEXT (("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceEventTypeEXT))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DeviceEventTypeEXT -> DeviceEventInfoEXT
DeviceEventInfoEXT
             DeviceEventTypeEXT
deviceEvent
instance Storable DeviceEventInfoEXT where
  sizeOf :: DeviceEventInfoEXT -> Int
sizeOf ~DeviceEventInfoEXT
_ = Int
24
  alignment :: DeviceEventInfoEXT -> Int
alignment ~DeviceEventInfoEXT
_ = Int
8
  peek :: ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
-> IO DeviceEventInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT)
-> DeviceEventInfoEXT -> IO ()
poke "pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
ptr DeviceEventInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pDeviceEventInfo" ::: Ptr DeviceEventInfoEXT
ptr DeviceEventInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DeviceEventInfoEXT where
  zero :: DeviceEventInfoEXT
zero = DeviceEventTypeEXT -> DeviceEventInfoEXT
DeviceEventInfoEXT
           forall a. Zero a => a
zero
data DisplayEventInfoEXT = DisplayEventInfoEXT
  { 
    
    
    
    
    DisplayEventInfoEXT -> DisplayEventTypeEXT
displayEvent :: DisplayEventTypeEXT }
  deriving (Typeable, DisplayEventInfoEXT -> DisplayEventInfoEXT -> Bool
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 :: forall b.
DisplayEventInfoEXT
-> (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT) -> IO b)
-> IO b
withCStruct DisplayEventInfoEXT
x ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p -> 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 :: forall b.
("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
-> DisplayEventInfoEXT -> IO b -> IO b
pokeCStruct "pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p DisplayEventInfoEXT{DisplayEventTypeEXT
displayEvent :: DisplayEventTypeEXT
$sel:displayEvent:DisplayEventInfoEXT :: DisplayEventInfoEXT -> DisplayEventTypeEXT
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DISPLAY_EVENT_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DisplayEventTypeEXT)) (DisplayEventTypeEXT
displayEvent)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DISPLAY_EVENT_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DisplayEventTypeEXT)) (forall a. Zero a => a
zero)
    IO b
f
instance FromCStruct DisplayEventInfoEXT where
  peekCStruct :: ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
-> IO DisplayEventInfoEXT
peekCStruct "pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p = do
    DisplayEventTypeEXT
displayEvent <- forall a. Storable a => Ptr a -> IO a
peek @DisplayEventTypeEXT (("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DisplayEventTypeEXT))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DisplayEventTypeEXT -> DisplayEventInfoEXT
DisplayEventInfoEXT
             DisplayEventTypeEXT
displayEvent
instance Storable DisplayEventInfoEXT where
  sizeOf :: DisplayEventInfoEXT -> Int
sizeOf ~DisplayEventInfoEXT
_ = Int
24
  alignment :: DisplayEventInfoEXT -> Int
alignment ~DisplayEventInfoEXT
_ = Int
8
  peek :: ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
-> IO DisplayEventInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: ("pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT)
-> DisplayEventInfoEXT -> IO ()
poke "pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
ptr DisplayEventInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pDisplayEventInfo" ::: Ptr DisplayEventInfoEXT
ptr DisplayEventInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DisplayEventInfoEXT where
  zero :: DisplayEventInfoEXT
zero = DisplayEventTypeEXT -> DisplayEventInfoEXT
DisplayEventInfoEXT
           forall a. Zero a => a
zero
data SwapchainCounterCreateInfoEXT = SwapchainCounterCreateInfoEXT
  { 
    
    
    SwapchainCounterCreateInfoEXT -> SurfaceCounterFlagBitsEXT
surfaceCounters :: SurfaceCounterFlagsEXT }
  deriving (Typeable, SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> Bool
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 :: forall b.
SwapchainCounterCreateInfoEXT
-> (Ptr SwapchainCounterCreateInfoEXT -> IO b) -> IO b
withCStruct SwapchainCounterCreateInfoEXT
x Ptr SwapchainCounterCreateInfoEXT -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr SwapchainCounterCreateInfoEXT
p -> 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 :: forall b.
Ptr SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr SwapchainCounterCreateInfoEXT
p SwapchainCounterCreateInfoEXT{SurfaceCounterFlagBitsEXT
surfaceCounters :: SurfaceCounterFlagBitsEXT
$sel:surfaceCounters:SwapchainCounterCreateInfoEXT :: SwapchainCounterCreateInfoEXT -> SurfaceCounterFlagBitsEXT
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_COUNTER_CREATE_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceCounterFlagsEXT)) (SurfaceCounterFlagBitsEXT
surfaceCounters)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr SwapchainCounterCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr SwapchainCounterCreateInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_COUNTER_CREATE_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainCounterCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f
instance FromCStruct SwapchainCounterCreateInfoEXT where
  peekCStruct :: Ptr SwapchainCounterCreateInfoEXT
-> IO SwapchainCounterCreateInfoEXT
peekCStruct Ptr SwapchainCounterCreateInfoEXT
p = do
    SurfaceCounterFlagBitsEXT
surfaceCounters <- forall a. Storable a => Ptr a -> IO a
peek @SurfaceCounterFlagsEXT ((Ptr SwapchainCounterCreateInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr SurfaceCounterFlagsEXT))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ SurfaceCounterFlagBitsEXT -> SwapchainCounterCreateInfoEXT
SwapchainCounterCreateInfoEXT
             SurfaceCounterFlagBitsEXT
surfaceCounters
instance Storable SwapchainCounterCreateInfoEXT where
  sizeOf :: SwapchainCounterCreateInfoEXT -> Int
sizeOf ~SwapchainCounterCreateInfoEXT
_ = Int
24
  alignment :: SwapchainCounterCreateInfoEXT -> Int
alignment ~SwapchainCounterCreateInfoEXT
_ = Int
8
  peek :: Ptr SwapchainCounterCreateInfoEXT
-> IO SwapchainCounterCreateInfoEXT
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr SwapchainCounterCreateInfoEXT
-> SwapchainCounterCreateInfoEXT -> IO ()
poke Ptr SwapchainCounterCreateInfoEXT
ptr SwapchainCounterCreateInfoEXT
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SwapchainCounterCreateInfoEXT
ptr SwapchainCounterCreateInfoEXT
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SwapchainCounterCreateInfoEXT where
  zero :: SwapchainCounterCreateInfoEXT
zero = SurfaceCounterFlagBitsEXT -> SwapchainCounterCreateInfoEXT
SwapchainCounterCreateInfoEXT
           forall a. Zero a => a
zero
newtype DisplayPowerStateEXT = DisplayPowerStateEXT Int32
  deriving newtype (DisplayPowerStateEXT -> DisplayPowerStateEXT -> Bool
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
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
Ord, Ptr DisplayPowerStateEXT -> IO DisplayPowerStateEXT
Ptr DisplayPowerStateEXT -> Int -> IO DisplayPowerStateEXT
Ptr DisplayPowerStateEXT -> Int -> DisplayPowerStateEXT -> IO ()
Ptr DisplayPowerStateEXT -> DisplayPowerStateEXT -> IO ()
DisplayPowerStateEXT -> Int
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 :: forall b. Ptr b -> Int -> DisplayPowerStateEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayPowerStateEXT -> IO ()
peekByteOff :: forall b. 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
forall a. a -> Zero a
zero :: DisplayPowerStateEXT
$czero :: DisplayPowerStateEXT
Zero)
pattern $bDISPLAY_POWER_STATE_OFF_EXT :: DisplayPowerStateEXT
$mDISPLAY_POWER_STATE_OFF_EXT :: forall {r}.
DisplayPowerStateEXT -> ((# #) -> r) -> ((# #) -> r) -> r
DISPLAY_POWER_STATE_OFF_EXT = DisplayPowerStateEXT 0
pattern $bDISPLAY_POWER_STATE_SUSPEND_EXT :: DisplayPowerStateEXT
$mDISPLAY_POWER_STATE_SUSPEND_EXT :: forall {r}.
DisplayPowerStateEXT -> ((# #) -> r) -> ((# #) -> r) -> r
DISPLAY_POWER_STATE_SUSPEND_EXT = DisplayPowerStateEXT 1
pattern $bDISPLAY_POWER_STATE_ON_EXT :: DisplayPowerStateEXT
$mDISPLAY_POWER_STATE_ON_EXT :: forall {r}.
DisplayPowerStateEXT -> ((# #) -> r) -> ((# #) -> 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
  #-}
conNameDisplayPowerStateEXT :: String
conNameDisplayPowerStateEXT :: String
conNameDisplayPowerStateEXT = String
"DisplayPowerStateEXT"
enumPrefixDisplayPowerStateEXT :: String
enumPrefixDisplayPowerStateEXT :: String
enumPrefixDisplayPowerStateEXT = String
"DISPLAY_POWER_STATE_"
showTableDisplayPowerStateEXT :: [(DisplayPowerStateEXT, String)]
showTableDisplayPowerStateEXT :: [(DisplayPowerStateEXT, String)]
showTableDisplayPowerStateEXT =
  [ (DisplayPowerStateEXT
DISPLAY_POWER_STATE_OFF_EXT, String
"OFF_EXT")
  ,
    ( DisplayPowerStateEXT
DISPLAY_POWER_STATE_SUSPEND_EXT
    , String
"SUSPEND_EXT"
    )
  , (DisplayPowerStateEXT
DISPLAY_POWER_STATE_ON_EXT, String
"ON_EXT")
  ]
instance Show DisplayPowerStateEXT where
  showsPrec :: Int -> DisplayPowerStateEXT -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixDisplayPowerStateEXT
      [(DisplayPowerStateEXT, String)]
showTableDisplayPowerStateEXT
      String
conNameDisplayPowerStateEXT
      (\(DisplayPowerStateEXT Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)
instance Read DisplayPowerStateEXT where
  readPrec :: ReadPrec DisplayPowerStateEXT
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixDisplayPowerStateEXT
      [(DisplayPowerStateEXT, String)]
showTableDisplayPowerStateEXT
      String
conNameDisplayPowerStateEXT
      Int32 -> DisplayPowerStateEXT
DisplayPowerStateEXT
newtype DeviceEventTypeEXT = DeviceEventTypeEXT Int32
  deriving newtype (DeviceEventTypeEXT -> DeviceEventTypeEXT -> Bool
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
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
Ord, Ptr DeviceEventTypeEXT -> IO DeviceEventTypeEXT
Ptr DeviceEventTypeEXT -> Int -> IO DeviceEventTypeEXT
Ptr DeviceEventTypeEXT -> Int -> DeviceEventTypeEXT -> IO ()
Ptr DeviceEventTypeEXT -> DeviceEventTypeEXT -> IO ()
DeviceEventTypeEXT -> Int
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 :: forall b. Ptr b -> Int -> DeviceEventTypeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DeviceEventTypeEXT -> IO ()
peekByteOff :: forall b. 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
forall a. a -> Zero a
zero :: DeviceEventTypeEXT
$czero :: DeviceEventTypeEXT
Zero)
pattern $bDEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT :: DeviceEventTypeEXT
$mDEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT :: forall {r}. DeviceEventTypeEXT -> ((# #) -> r) -> ((# #) -> r) -> r
DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT = DeviceEventTypeEXT 0
{-# COMPLETE DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT :: DeviceEventTypeEXT #-}
conNameDeviceEventTypeEXT :: String
conNameDeviceEventTypeEXT :: String
conNameDeviceEventTypeEXT = String
"DeviceEventTypeEXT"
enumPrefixDeviceEventTypeEXT :: String
enumPrefixDeviceEventTypeEXT :: String
enumPrefixDeviceEventTypeEXT = String
"DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT"
showTableDeviceEventTypeEXT :: [(DeviceEventTypeEXT, String)]
showTableDeviceEventTypeEXT :: [(DeviceEventTypeEXT, String)]
showTableDeviceEventTypeEXT = [(DeviceEventTypeEXT
DEVICE_EVENT_TYPE_DISPLAY_HOTPLUG_EXT, String
"")]
instance Show DeviceEventTypeEXT where
  showsPrec :: Int -> DeviceEventTypeEXT -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixDeviceEventTypeEXT
      [(DeviceEventTypeEXT, String)]
showTableDeviceEventTypeEXT
      String
conNameDeviceEventTypeEXT
      (\(DeviceEventTypeEXT Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)
instance Read DeviceEventTypeEXT where
  readPrec :: ReadPrec DeviceEventTypeEXT
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixDeviceEventTypeEXT
      [(DeviceEventTypeEXT, String)]
showTableDeviceEventTypeEXT
      String
conNameDeviceEventTypeEXT
      Int32 -> DeviceEventTypeEXT
DeviceEventTypeEXT
newtype DisplayEventTypeEXT = DisplayEventTypeEXT Int32
  deriving newtype (DisplayEventTypeEXT -> DisplayEventTypeEXT -> Bool
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
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
Ord, Ptr DisplayEventTypeEXT -> IO DisplayEventTypeEXT
Ptr DisplayEventTypeEXT -> Int -> IO DisplayEventTypeEXT
Ptr DisplayEventTypeEXT -> Int -> DisplayEventTypeEXT -> IO ()
Ptr DisplayEventTypeEXT -> DisplayEventTypeEXT -> IO ()
DisplayEventTypeEXT -> Int
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 :: forall b. Ptr b -> Int -> DisplayEventTypeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayEventTypeEXT -> IO ()
peekByteOff :: forall b. 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
forall a. a -> Zero a
zero :: DisplayEventTypeEXT
$czero :: DisplayEventTypeEXT
Zero)
pattern $bDISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT :: DisplayEventTypeEXT
$mDISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT :: forall {r}.
DisplayEventTypeEXT -> ((# #) -> r) -> ((# #) -> r) -> r
DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT = DisplayEventTypeEXT 0
{-# COMPLETE DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT :: DisplayEventTypeEXT #-}
conNameDisplayEventTypeEXT :: String
conNameDisplayEventTypeEXT :: String
conNameDisplayEventTypeEXT = String
"DisplayEventTypeEXT"
enumPrefixDisplayEventTypeEXT :: String
enumPrefixDisplayEventTypeEXT :: String
enumPrefixDisplayEventTypeEXT = String
"DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT"
showTableDisplayEventTypeEXT :: [(DisplayEventTypeEXT, String)]
showTableDisplayEventTypeEXT :: [(DisplayEventTypeEXT, String)]
showTableDisplayEventTypeEXT = [(DisplayEventTypeEXT
DISPLAY_EVENT_TYPE_FIRST_PIXEL_OUT_EXT, String
"")]
instance Show DisplayEventTypeEXT where
  showsPrec :: Int -> DisplayEventTypeEXT -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixDisplayEventTypeEXT
      [(DisplayEventTypeEXT, String)]
showTableDisplayEventTypeEXT
      String
conNameDisplayEventTypeEXT
      (\(DisplayEventTypeEXT Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)
instance Read DisplayEventTypeEXT where
  readPrec :: ReadPrec DisplayEventTypeEXT
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixDisplayEventTypeEXT
      [(DisplayEventTypeEXT, String)]
showTableDisplayEventTypeEXT
      String
conNameDisplayEventTypeEXT
      Int32 -> DisplayEventTypeEXT
DisplayEventTypeEXT
type EXT_DISPLAY_CONTROL_SPEC_VERSION = 1
pattern EXT_DISPLAY_CONTROL_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DISPLAY_CONTROL_SPEC_VERSION :: forall a. Integral a => a
$mEXT_DISPLAY_CONTROL_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DISPLAY_CONTROL_SPEC_VERSION = 1
type EXT_DISPLAY_CONTROL_EXTENSION_NAME = "VK_EXT_display_control"
pattern EXT_DISPLAY_CONTROL_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DISPLAY_CONTROL_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_DISPLAY_CONTROL_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DISPLAY_CONTROL_EXTENSION_NAME = "VK_EXT_display_control"