{-# language CPP #-}
module Vulkan.Extensions.VK_NV_low_latency2 ( setLatencySleepModeNV
, latencySleepNV
, setLatencyMarkerNV
, getLatencyTimingsNV
, queueNotifyOutOfBandNV
, LatencySleepModeInfoNV(..)
, LatencySleepInfoNV(..)
, SetLatencyMarkerInfoNV(..)
, GetLatencyMarkerInfoNV(..)
, LatencyTimingsFrameReportNV(..)
, OutOfBandQueueTypeInfoNV(..)
, LatencySubmissionPresentIdNV(..)
, SwapchainLatencyCreateInfoNV(..)
, LatencySurfaceCapabilitiesNV(..)
, LatencyMarkerNV( LATENCY_MARKER_SIMULATION_START_NV
, LATENCY_MARKER_SIMULATION_END_NV
, LATENCY_MARKER_RENDERSUBMIT_START_NV
, LATENCY_MARKER_RENDERSUBMIT_END_NV
, LATENCY_MARKER_PRESENT_START_NV
, LATENCY_MARKER_PRESENT_END_NV
, LATENCY_MARKER_INPUT_SAMPLE_NV
, LATENCY_MARKER_TRIGGER_FLASH_NV
, LATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_START_NV
, LATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_END_NV
, LATENCY_MARKER_OUT_OF_BAND_PRESENT_START_NV
, LATENCY_MARKER_OUT_OF_BAND_PRESENT_END_NV
, ..
)
, OutOfBandQueueTypeNV( OUT_OF_BAND_QUEUE_TYPE_RENDER_NV
, OUT_OF_BAND_QUEUE_TYPE_PRESENT_NV
, ..
)
, NV_LOW_LATENCY_2_SPEC_VERSION
, pattern NV_LOW_LATENCY_2_SPEC_VERSION
, NV_LOW_LATENCY_2_EXTENSION_NAME
, pattern NV_LOW_LATENCY_2_EXTENSION_NAME
, SwapchainKHR(..)
, PresentModeKHR(..)
) 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 (Word32)
import Data.Word (Word64)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetLatencyTimingsNV))
import Vulkan.Dynamic (DeviceCmds(pVkLatencySleepNV))
import Vulkan.Dynamic (DeviceCmds(pVkQueueNotifyOutOfBandNV))
import Vulkan.Dynamic (DeviceCmds(pVkSetLatencyMarkerNV))
import Vulkan.Dynamic (DeviceCmds(pVkSetLatencySleepModeNV))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Extensions.VK_KHR_surface (PresentModeKHR)
import Vulkan.Core10.Handles (Queue)
import Vulkan.Core10.Handles (Queue(..))
import Vulkan.Core10.Handles (Queue(Queue))
import Vulkan.Core10.Handles (Queue_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Handles (Semaphore)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Extensions.Handles (SwapchainKHR)
import Vulkan.Extensions.Handles (SwapchainKHR(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_GET_LATENCY_MARKER_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_LATENCY_SLEEP_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_LATENCY_SLEEP_MODE_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_LATENCY_SUBMISSION_PRESENT_ID_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_LATENCY_SURFACE_CAPABILITIES_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_LATENCY_TIMINGS_FRAME_REPORT_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_OUT_OF_BAND_QUEUE_TYPE_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SET_LATENCY_MARKER_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SWAPCHAIN_LATENCY_CREATE_INFO_NV))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_KHR_surface (PresentModeKHR(..))
import Vulkan.Extensions.Handles (SwapchainKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkSetLatencySleepModeNV
:: FunPtr (Ptr Device_T -> SwapchainKHR -> Ptr LatencySleepModeInfoNV -> IO Result) -> Ptr Device_T -> SwapchainKHR -> Ptr LatencySleepModeInfoNV -> IO Result
setLatencySleepModeNV :: forall io
. (MonadIO io)
=>
Device
->
SwapchainKHR
->
LatencySleepModeInfoNV
-> io ()
setLatencySleepModeNV :: forall (io :: * -> *).
MonadIO io =>
Device -> SwapchainKHR -> LatencySleepModeInfoNV -> io ()
setLatencySleepModeNV Device
device SwapchainKHR
swapchain LatencySleepModeInfoNV
sleepModeInfo = 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 vkSetLatencySleepModeNVPtr :: FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO Result)
vkSetLatencySleepModeNVPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO Result)
pVkSetLatencySleepModeNV (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
-> SwapchainKHR
-> ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO Result)
vkSetLatencySleepModeNVPtr 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 vkSetLatencySleepModeNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkSetLatencySleepModeNV' :: Ptr Device_T
-> SwapchainKHR
-> ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO Result
vkSetLatencySleepModeNV' = FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO Result)
-> Ptr Device_T
-> SwapchainKHR
-> ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO Result
mkVkSetLatencySleepModeNV FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO Result)
vkSetLatencySleepModeNVPtr
"pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
pSleepModeInfo <- 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 (LatencySleepModeInfoNV
sleepModeInfo)
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
"vkSetLatencySleepModeNV" (Ptr Device_T
-> SwapchainKHR
-> ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO Result
vkSetLatencySleepModeNV'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(SwapchainKHR
swapchain)
"pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
pSleepModeInfo)
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" mkVkLatencySleepNV
:: FunPtr (Ptr Device_T -> SwapchainKHR -> Ptr LatencySleepInfoNV -> IO Result) -> Ptr Device_T -> SwapchainKHR -> Ptr LatencySleepInfoNV -> IO Result
latencySleepNV :: forall io
. (MonadIO io)
=>
Device
->
SwapchainKHR
->
LatencySleepInfoNV
-> io ()
latencySleepNV :: forall (io :: * -> *).
MonadIO io =>
Device -> SwapchainKHR -> LatencySleepInfoNV -> io ()
latencySleepNV Device
device SwapchainKHR
swapchain LatencySleepInfoNV
sleepInfo = 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 vkLatencySleepNVPtr :: FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> IO Result)
vkLatencySleepNVPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> IO Result)
pVkLatencySleepNV (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
-> ("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> IO Result)
vkLatencySleepNVPtr 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 vkLatencySleepNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkLatencySleepNV' :: Ptr Device_T
-> SwapchainKHR
-> ("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> IO Result
vkLatencySleepNV' = FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> IO Result)
-> Ptr Device_T
-> SwapchainKHR
-> ("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> IO Result
mkVkLatencySleepNV FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> IO Result)
vkLatencySleepNVPtr
"pSleepInfo" ::: Ptr LatencySleepInfoNV
pSleepInfo <- 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 (LatencySleepInfoNV
sleepInfo)
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
"vkLatencySleepNV" (Ptr Device_T
-> SwapchainKHR
-> ("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> IO Result
vkLatencySleepNV'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(SwapchainKHR
swapchain)
"pSleepInfo" ::: Ptr LatencySleepInfoNV
pSleepInfo)
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" mkVkSetLatencyMarkerNV
:: FunPtr (Ptr Device_T -> SwapchainKHR -> Ptr SetLatencyMarkerInfoNV -> IO ()) -> Ptr Device_T -> SwapchainKHR -> Ptr SetLatencyMarkerInfoNV -> IO ()
setLatencyMarkerNV :: forall io
. (MonadIO io)
=>
Device
->
SwapchainKHR
->
SetLatencyMarkerInfoNV
-> io ()
setLatencyMarkerNV :: forall (io :: * -> *).
MonadIO io =>
Device -> SwapchainKHR -> SetLatencyMarkerInfoNV -> io ()
setLatencyMarkerNV Device
device SwapchainKHR
swapchain SetLatencyMarkerInfoNV
latencyMarkerInfo = 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 vkSetLatencyMarkerNVPtr :: FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO ())
vkSetLatencyMarkerNVPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO ())
pVkSetLatencyMarkerNV (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
-> ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO ())
vkSetLatencyMarkerNVPtr 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 vkSetLatencyMarkerNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkSetLatencyMarkerNV' :: Ptr Device_T
-> SwapchainKHR
-> ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO ()
vkSetLatencyMarkerNV' = FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO ())
-> Ptr Device_T
-> SwapchainKHR
-> ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO ()
mkVkSetLatencyMarkerNV FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO ())
vkSetLatencyMarkerNVPtr
"pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
pLatencyMarkerInfo <- 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 (SetLatencyMarkerInfoNV
latencyMarkerInfo)
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
"vkSetLatencyMarkerNV" (Ptr Device_T
-> SwapchainKHR
-> ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO ()
vkSetLatencyMarkerNV'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(SwapchainKHR
swapchain)
"pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
pLatencyMarkerInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetLatencyTimingsNV
:: FunPtr (Ptr Device_T -> SwapchainKHR -> Ptr Word32 -> Ptr GetLatencyMarkerInfoNV -> IO ()) -> Ptr Device_T -> SwapchainKHR -> Ptr Word32 -> Ptr GetLatencyMarkerInfoNV -> IO ()
getLatencyTimingsNV :: forall io
. (MonadIO io)
=>
Device
->
SwapchainKHR
-> io (("timingCount" ::: Word32), GetLatencyMarkerInfoNV)
getLatencyTimingsNV :: forall (io :: * -> *).
MonadIO io =>
Device
-> SwapchainKHR
-> io ("timingCount" ::: Word32, GetLatencyMarkerInfoNV)
getLatencyTimingsNV Device
device SwapchainKHR
swapchain = 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 vkGetLatencyTimingsNVPtr :: FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pTimingCount" ::: Ptr ("timingCount" ::: Word32))
-> ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO ())
vkGetLatencyTimingsNVPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pTimingCount" ::: Ptr ("timingCount" ::: Word32))
-> ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO ())
pVkGetLatencyTimingsNV (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
-> ("pTimingCount" ::: Ptr ("timingCount" ::: Word32))
-> ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO ())
vkGetLatencyTimingsNVPtr 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 vkGetLatencyTimingsNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkGetLatencyTimingsNV' :: Ptr Device_T
-> SwapchainKHR
-> ("pTimingCount" ::: Ptr ("timingCount" ::: Word32))
-> ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO ()
vkGetLatencyTimingsNV' = FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pTimingCount" ::: Ptr ("timingCount" ::: Word32))
-> ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO ())
-> Ptr Device_T
-> SwapchainKHR
-> ("pTimingCount" ::: Ptr ("timingCount" ::: Word32))
-> ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO ()
mkVkGetLatencyTimingsNV FunPtr
(Ptr Device_T
-> SwapchainKHR
-> ("pTimingCount" ::: Ptr ("timingCount" ::: Word32))
-> ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO ())
vkGetLatencyTimingsNVPtr
"pTimingCount" ::: Ptr ("timingCount" ::: Word32)
pPTimingCount <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Word32 Int
4) forall a. Ptr a -> IO ()
free
"pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
pPLatencyMarkerInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @GetLatencyMarkerInfoNV)
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
"vkGetLatencyTimingsNV" (Ptr Device_T
-> SwapchainKHR
-> ("pTimingCount" ::: Ptr ("timingCount" ::: Word32))
-> ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO ()
vkGetLatencyTimingsNV'
(Device -> Ptr Device_T
deviceHandle (Device
device))
(SwapchainKHR
swapchain)
("pTimingCount" ::: Ptr ("timingCount" ::: Word32)
pPTimingCount)
("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
pPLatencyMarkerInfo))
"timingCount" ::: Word32
pTimingCount <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word32 "pTimingCount" ::: Ptr ("timingCount" ::: Word32)
pPTimingCount
GetLatencyMarkerInfoNV
pLatencyMarkerInfo <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @GetLatencyMarkerInfoNV "pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
pPLatencyMarkerInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("timingCount" ::: Word32
pTimingCount, GetLatencyMarkerInfoNV
pLatencyMarkerInfo)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkQueueNotifyOutOfBandNV
:: FunPtr (Ptr Queue_T -> Ptr OutOfBandQueueTypeInfoNV -> IO ()) -> Ptr Queue_T -> Ptr OutOfBandQueueTypeInfoNV -> IO ()
queueNotifyOutOfBandNV :: forall io
. (MonadIO io)
=>
Queue
->
OutOfBandQueueTypeInfoNV
-> io ()
queueNotifyOutOfBandNV :: forall (io :: * -> *).
MonadIO io =>
Queue -> OutOfBandQueueTypeInfoNV -> io ()
queueNotifyOutOfBandNV Queue
queue OutOfBandQueueTypeInfoNV
queueTypeInfo = 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 vkQueueNotifyOutOfBandNVPtr :: FunPtr
(Ptr Queue_T
-> ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO ())
vkQueueNotifyOutOfBandNVPtr = DeviceCmds
-> FunPtr
(Ptr Queue_T
-> ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO ())
pVkQueueNotifyOutOfBandNV (case Queue
queue of Queue{DeviceCmds
$sel:deviceCmds:Queue :: Queue -> 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 Queue_T
-> ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO ())
vkQueueNotifyOutOfBandNVPtr 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 vkQueueNotifyOutOfBandNV is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
let vkQueueNotifyOutOfBandNV' :: Ptr Queue_T
-> ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO ()
vkQueueNotifyOutOfBandNV' = FunPtr
(Ptr Queue_T
-> ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO ())
-> Ptr Queue_T
-> ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV)
-> IO ()
mkVkQueueNotifyOutOfBandNV FunPtr
(Ptr Queue_T
-> ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO ())
vkQueueNotifyOutOfBandNVPtr
"pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
pQueueTypeInfo <- 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 (OutOfBandQueueTypeInfoNV
queueTypeInfo)
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
"vkQueueNotifyOutOfBandNV" (Ptr Queue_T
-> ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO ()
vkQueueNotifyOutOfBandNV'
(Queue -> Ptr Queue_T
queueHandle (Queue
queue))
"pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
pQueueTypeInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()
data LatencySleepModeInfoNV = LatencySleepModeInfoNV
{
LatencySleepModeInfoNV -> Bool
lowLatencyMode :: Bool
,
LatencySleepModeInfoNV -> Bool
lowLatencyBoost :: Bool
,
LatencySleepModeInfoNV -> "timingCount" ::: Word32
minimumIntervalUs :: Word32
}
deriving (Typeable, LatencySleepModeInfoNV -> LatencySleepModeInfoNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LatencySleepModeInfoNV -> LatencySleepModeInfoNV -> Bool
$c/= :: LatencySleepModeInfoNV -> LatencySleepModeInfoNV -> Bool
== :: LatencySleepModeInfoNV -> LatencySleepModeInfoNV -> Bool
$c== :: LatencySleepModeInfoNV -> LatencySleepModeInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (LatencySleepModeInfoNV)
#endif
deriving instance Show LatencySleepModeInfoNV
instance ToCStruct LatencySleepModeInfoNV where
withCStruct :: forall b.
LatencySleepModeInfoNV
-> (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV) -> IO b)
-> IO b
withCStruct LatencySleepModeInfoNV
x ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p LatencySleepModeInfoNV
x (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV) -> IO b
f "pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p)
pokeCStruct :: forall b.
("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> LatencySleepModeInfoNV -> IO b -> IO b
pokeCStruct "pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p LatencySleepModeInfoNV{Bool
"timingCount" ::: Word32
minimumIntervalUs :: "timingCount" ::: Word32
lowLatencyBoost :: Bool
lowLatencyMode :: Bool
$sel:minimumIntervalUs:LatencySleepModeInfoNV :: LatencySleepModeInfoNV -> "timingCount" ::: Word32
$sel:lowLatencyBoost:LatencySleepModeInfoNV :: LatencySleepModeInfoNV -> Bool
$sel:lowLatencyMode:LatencySleepModeInfoNV :: LatencySleepModeInfoNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_SLEEP_MODE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
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 (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
lowLatencyMode))
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
lowLatencyBoost))
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) ("timingCount" ::: Word32
minimumIntervalUs)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV) -> IO b -> IO b
pokeZeroCStruct "pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_SLEEP_MODE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
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 (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct LatencySleepModeInfoNV where
peekCStruct :: ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO LatencySleepModeInfoNV
peekCStruct "pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p = do
Bool32
lowLatencyMode <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
Bool32
lowLatencyBoost <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
"timingCount" ::: Word32
minimumIntervalUs <- forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool
-> Bool -> ("timingCount" ::: Word32) -> LatencySleepModeInfoNV
LatencySleepModeInfoNV
(Bool32 -> Bool
bool32ToBool Bool32
lowLatencyMode)
(Bool32 -> Bool
bool32ToBool Bool32
lowLatencyBoost)
"timingCount" ::: Word32
minimumIntervalUs
instance Storable LatencySleepModeInfoNV where
sizeOf :: LatencySleepModeInfoNV -> Int
sizeOf ~LatencySleepModeInfoNV
_ = Int
32
alignment :: LatencySleepModeInfoNV -> Int
alignment ~LatencySleepModeInfoNV
_ = Int
8
peek :: ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> IO LatencySleepModeInfoNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV)
-> LatencySleepModeInfoNV -> IO ()
poke "pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
ptr LatencySleepModeInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSleepModeInfo" ::: Ptr LatencySleepModeInfoNV
ptr LatencySleepModeInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero LatencySleepModeInfoNV where
zero :: LatencySleepModeInfoNV
zero = Bool
-> Bool -> ("timingCount" ::: Word32) -> LatencySleepModeInfoNV
LatencySleepModeInfoNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data LatencySleepInfoNV = LatencySleepInfoNV
{
LatencySleepInfoNV -> Semaphore
signalSemaphore :: Semaphore
,
LatencySleepInfoNV -> Word64
value :: Word64
}
deriving (Typeable, LatencySleepInfoNV -> LatencySleepInfoNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LatencySleepInfoNV -> LatencySleepInfoNV -> Bool
$c/= :: LatencySleepInfoNV -> LatencySleepInfoNV -> Bool
== :: LatencySleepInfoNV -> LatencySleepInfoNV -> Bool
$c== :: LatencySleepInfoNV -> LatencySleepInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (LatencySleepInfoNV)
#endif
deriving instance Show LatencySleepInfoNV
instance ToCStruct LatencySleepInfoNV where
withCStruct :: forall b.
LatencySleepInfoNV
-> (("pSleepInfo" ::: Ptr LatencySleepInfoNV) -> IO b) -> IO b
withCStruct LatencySleepInfoNV
x ("pSleepInfo" ::: Ptr LatencySleepInfoNV) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pSleepInfo" ::: Ptr LatencySleepInfoNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSleepInfo" ::: Ptr LatencySleepInfoNV
p LatencySleepInfoNV
x (("pSleepInfo" ::: Ptr LatencySleepInfoNV) -> IO b
f "pSleepInfo" ::: Ptr LatencySleepInfoNV
p)
pokeCStruct :: forall b.
("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> LatencySleepInfoNV -> IO b -> IO b
pokeCStruct "pSleepInfo" ::: Ptr LatencySleepInfoNV
p LatencySleepInfoNV{Word64
Semaphore
value :: Word64
signalSemaphore :: Semaphore
$sel:value:LatencySleepInfoNV :: LatencySleepInfoNV -> Word64
$sel:signalSemaphore:LatencySleepInfoNV :: LatencySleepInfoNV -> Semaphore
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepInfo" ::: Ptr LatencySleepInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_SLEEP_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepInfo" ::: Ptr LatencySleepInfoNV
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 (("pSleepInfo" ::: Ptr LatencySleepInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Semaphore)) (Semaphore
signalSemaphore)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepInfo" ::: Ptr LatencySleepInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
value)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. ("pSleepInfo" ::: Ptr LatencySleepInfoNV) -> IO b -> IO b
pokeZeroCStruct "pSleepInfo" ::: Ptr LatencySleepInfoNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepInfo" ::: Ptr LatencySleepInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_SLEEP_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepInfo" ::: Ptr LatencySleepInfoNV
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 (("pSleepInfo" ::: Ptr LatencySleepInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Semaphore)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSleepInfo" ::: Ptr LatencySleepInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct LatencySleepInfoNV where
peekCStruct :: ("pSleepInfo" ::: Ptr LatencySleepInfoNV) -> IO LatencySleepInfoNV
peekCStruct "pSleepInfo" ::: Ptr LatencySleepInfoNV
p = do
Semaphore
signalSemaphore <- forall a. Storable a => Ptr a -> IO a
peek @Semaphore (("pSleepInfo" ::: Ptr LatencySleepInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Semaphore))
Word64
value <- forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pSleepInfo" ::: Ptr LatencySleepInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Semaphore -> Word64 -> LatencySleepInfoNV
LatencySleepInfoNV
Semaphore
signalSemaphore Word64
value
instance Storable LatencySleepInfoNV where
sizeOf :: LatencySleepInfoNV -> Int
sizeOf ~LatencySleepInfoNV
_ = Int
32
alignment :: LatencySleepInfoNV -> Int
alignment ~LatencySleepInfoNV
_ = Int
8
peek :: ("pSleepInfo" ::: Ptr LatencySleepInfoNV) -> IO LatencySleepInfoNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pSleepInfo" ::: Ptr LatencySleepInfoNV)
-> LatencySleepInfoNV -> IO ()
poke "pSleepInfo" ::: Ptr LatencySleepInfoNV
ptr LatencySleepInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSleepInfo" ::: Ptr LatencySleepInfoNV
ptr LatencySleepInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero LatencySleepInfoNV where
zero :: LatencySleepInfoNV
zero = Semaphore -> Word64 -> LatencySleepInfoNV
LatencySleepInfoNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data SetLatencyMarkerInfoNV = SetLatencyMarkerInfoNV
{
SetLatencyMarkerInfoNV -> Word64
presentID :: Word64
,
SetLatencyMarkerInfoNV -> LatencyMarkerNV
marker :: LatencyMarkerNV
}
deriving (Typeable, SetLatencyMarkerInfoNV -> SetLatencyMarkerInfoNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetLatencyMarkerInfoNV -> SetLatencyMarkerInfoNV -> Bool
$c/= :: SetLatencyMarkerInfoNV -> SetLatencyMarkerInfoNV -> Bool
== :: SetLatencyMarkerInfoNV -> SetLatencyMarkerInfoNV -> Bool
$c== :: SetLatencyMarkerInfoNV -> SetLatencyMarkerInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SetLatencyMarkerInfoNV)
#endif
deriving instance Show SetLatencyMarkerInfoNV
instance ToCStruct SetLatencyMarkerInfoNV where
withCStruct :: forall b.
SetLatencyMarkerInfoNV
-> (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV) -> IO b)
-> IO b
withCStruct SetLatencyMarkerInfoNV
x ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p SetLatencyMarkerInfoNV
x (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV) -> IO b
f "pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p)
pokeCStruct :: forall b.
("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> SetLatencyMarkerInfoNV -> IO b -> IO b
pokeCStruct "pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p SetLatencyMarkerInfoNV{Word64
LatencyMarkerNV
marker :: LatencyMarkerNV
presentID :: Word64
$sel:marker:SetLatencyMarkerInfoNV :: SetLatencyMarkerInfoNV -> LatencyMarkerNV
$sel:presentID:SetLatencyMarkerInfoNV :: SetLatencyMarkerInfoNV -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SET_LATENCY_MARKER_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
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 (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
presentID)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr LatencyMarkerNV)) (LatencyMarkerNV
marker)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO b -> IO b
pokeZeroCStruct "pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SET_LATENCY_MARKER_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
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 (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr LatencyMarkerNV)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct SetLatencyMarkerInfoNV where
peekCStruct :: ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO SetLatencyMarkerInfoNV
peekCStruct "pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p = do
Word64
presentID <- forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
LatencyMarkerNV
marker <- forall a. Storable a => Ptr a -> IO a
peek @LatencyMarkerNV (("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr LatencyMarkerNV))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64 -> LatencyMarkerNV -> SetLatencyMarkerInfoNV
SetLatencyMarkerInfoNV
Word64
presentID LatencyMarkerNV
marker
instance Storable SetLatencyMarkerInfoNV where
sizeOf :: SetLatencyMarkerInfoNV -> Int
sizeOf ~SetLatencyMarkerInfoNV
_ = Int
32
alignment :: SetLatencyMarkerInfoNV -> Int
alignment ~SetLatencyMarkerInfoNV
_ = Int
8
peek :: ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> IO SetLatencyMarkerInfoNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV)
-> SetLatencyMarkerInfoNV -> IO ()
poke "pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
ptr SetLatencyMarkerInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pLatencyMarkerInfo" ::: Ptr SetLatencyMarkerInfoNV
ptr SetLatencyMarkerInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SetLatencyMarkerInfoNV where
zero :: SetLatencyMarkerInfoNV
zero = Word64 -> LatencyMarkerNV -> SetLatencyMarkerInfoNV
SetLatencyMarkerInfoNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data GetLatencyMarkerInfoNV = GetLatencyMarkerInfoNV
{
GetLatencyMarkerInfoNV -> Ptr LatencyTimingsFrameReportNV
timings :: Ptr LatencyTimingsFrameReportNV }
deriving (Typeable, GetLatencyMarkerInfoNV -> GetLatencyMarkerInfoNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLatencyMarkerInfoNV -> GetLatencyMarkerInfoNV -> Bool
$c/= :: GetLatencyMarkerInfoNV -> GetLatencyMarkerInfoNV -> Bool
== :: GetLatencyMarkerInfoNV -> GetLatencyMarkerInfoNV -> Bool
$c== :: GetLatencyMarkerInfoNV -> GetLatencyMarkerInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (GetLatencyMarkerInfoNV)
#endif
deriving instance Show GetLatencyMarkerInfoNV
instance ToCStruct GetLatencyMarkerInfoNV where
withCStruct :: forall b.
GetLatencyMarkerInfoNV
-> (("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV) -> IO b)
-> IO b
withCStruct GetLatencyMarkerInfoNV
x ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p GetLatencyMarkerInfoNV
x (("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV) -> IO b
f "pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p)
pokeCStruct :: forall b.
("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> GetLatencyMarkerInfoNV -> IO b -> IO b
pokeCStruct "pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p GetLatencyMarkerInfoNV{Ptr LatencyTimingsFrameReportNV
timings :: Ptr LatencyTimingsFrameReportNV
$sel:timings:GetLatencyMarkerInfoNV :: GetLatencyMarkerInfoNV -> Ptr LatencyTimingsFrameReportNV
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_GET_LATENCY_MARKER_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
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 (("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr LatencyTimingsFrameReportNV))) (Ptr LatencyTimingsFrameReportNV
timings)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO b -> IO b
pokeZeroCStruct "pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_GET_LATENCY_MARKER_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
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 (("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr LatencyTimingsFrameReportNV))) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct GetLatencyMarkerInfoNV where
peekCStruct :: ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO GetLatencyMarkerInfoNV
peekCStruct "pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p = do
Ptr LatencyTimingsFrameReportNV
pTimings <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr LatencyTimingsFrameReportNV) (("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr LatencyTimingsFrameReportNV)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Ptr LatencyTimingsFrameReportNV -> GetLatencyMarkerInfoNV
GetLatencyMarkerInfoNV
Ptr LatencyTimingsFrameReportNV
pTimings
instance Storable GetLatencyMarkerInfoNV where
sizeOf :: GetLatencyMarkerInfoNV -> Int
sizeOf ~GetLatencyMarkerInfoNV
_ = Int
24
alignment :: GetLatencyMarkerInfoNV -> Int
alignment ~GetLatencyMarkerInfoNV
_ = Int
8
peek :: ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> IO GetLatencyMarkerInfoNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV)
-> GetLatencyMarkerInfoNV -> IO ()
poke "pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
ptr GetLatencyMarkerInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pLatencyMarkerInfo" ::: Ptr GetLatencyMarkerInfoNV
ptr GetLatencyMarkerInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero GetLatencyMarkerInfoNV where
zero :: GetLatencyMarkerInfoNV
zero = Ptr LatencyTimingsFrameReportNV -> GetLatencyMarkerInfoNV
GetLatencyMarkerInfoNV
forall a. Zero a => a
zero
data LatencyTimingsFrameReportNV = LatencyTimingsFrameReportNV
{
LatencyTimingsFrameReportNV -> Word64
presentID :: Word64
,
LatencyTimingsFrameReportNV -> Word64
inputSampleTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
simStartTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
simEndTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
renderSubmitStartTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
renderSubmitEndTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
presentStartTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
presentEndTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
driverStartTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
driverEndTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
osRenderQueueStartTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
osRenderQueueEndTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
gpuRenderStartTimeUs :: Word64
,
LatencyTimingsFrameReportNV -> Word64
gpuRenderEndTimeUs :: Word64
}
deriving (Typeable, LatencyTimingsFrameReportNV -> LatencyTimingsFrameReportNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LatencyTimingsFrameReportNV -> LatencyTimingsFrameReportNV -> Bool
$c/= :: LatencyTimingsFrameReportNV -> LatencyTimingsFrameReportNV -> Bool
== :: LatencyTimingsFrameReportNV -> LatencyTimingsFrameReportNV -> Bool
$c== :: LatencyTimingsFrameReportNV -> LatencyTimingsFrameReportNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (LatencyTimingsFrameReportNV)
#endif
deriving instance Show LatencyTimingsFrameReportNV
instance ToCStruct LatencyTimingsFrameReportNV where
withCStruct :: forall b.
LatencyTimingsFrameReportNV
-> (Ptr LatencyTimingsFrameReportNV -> IO b) -> IO b
withCStruct LatencyTimingsFrameReportNV
x Ptr LatencyTimingsFrameReportNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
128 forall a b. (a -> b) -> a -> b
$ \Ptr LatencyTimingsFrameReportNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr LatencyTimingsFrameReportNV
p LatencyTimingsFrameReportNV
x (Ptr LatencyTimingsFrameReportNV -> IO b
f Ptr LatencyTimingsFrameReportNV
p)
pokeCStruct :: forall b.
Ptr LatencyTimingsFrameReportNV
-> LatencyTimingsFrameReportNV -> IO b -> IO b
pokeCStruct Ptr LatencyTimingsFrameReportNV
p LatencyTimingsFrameReportNV{Word64
gpuRenderEndTimeUs :: Word64
gpuRenderStartTimeUs :: Word64
osRenderQueueEndTimeUs :: Word64
osRenderQueueStartTimeUs :: Word64
driverEndTimeUs :: Word64
driverStartTimeUs :: Word64
presentEndTimeUs :: Word64
presentStartTimeUs :: Word64
renderSubmitEndTimeUs :: Word64
renderSubmitStartTimeUs :: Word64
simEndTimeUs :: Word64
simStartTimeUs :: Word64
inputSampleTimeUs :: Word64
presentID :: Word64
$sel:gpuRenderEndTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:gpuRenderStartTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:osRenderQueueEndTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:osRenderQueueStartTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:driverEndTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:driverStartTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:presentEndTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:presentStartTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:renderSubmitEndTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:renderSubmitStartTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:simEndTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:simStartTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:inputSampleTimeUs:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
$sel:presentID:LatencyTimingsFrameReportNV :: LatencyTimingsFrameReportNV -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_TIMINGS_FRAME_REPORT_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
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 LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
presentID)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
inputSampleTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word64)) (Word64
simStartTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word64)) (Word64
simEndTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word64)) (Word64
renderSubmitStartTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word64)) (Word64
renderSubmitEndTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Word64)) (Word64
presentStartTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Word64)) (Word64
presentEndTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Word64)) (Word64
driverStartTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Word64)) (Word64
driverEndTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Word64)) (Word64
osRenderQueueStartTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Word64)) (Word64
osRenderQueueEndTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Word64)) (Word64
gpuRenderStartTimeUs)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Word64)) (Word64
gpuRenderEndTimeUs)
IO b
f
cStructSize :: Int
cStructSize = Int
128
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr LatencyTimingsFrameReportNV -> IO b -> IO b
pokeZeroCStruct Ptr LatencyTimingsFrameReportNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_TIMINGS_FRAME_REPORT_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
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 LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Word64)) (forall a. Zero a => a
zero)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct LatencyTimingsFrameReportNV where
peekCStruct :: Ptr LatencyTimingsFrameReportNV -> IO LatencyTimingsFrameReportNV
peekCStruct Ptr LatencyTimingsFrameReportNV
p = do
Word64
presentID <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
Word64
inputSampleTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
Word64
simStartTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word64))
Word64
simEndTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word64))
Word64
renderSubmitStartTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word64))
Word64
renderSubmitEndTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word64))
Word64
presentStartTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr Word64))
Word64
presentEndTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr Word64))
Word64
driverStartTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr Word64))
Word64
driverEndTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr Word64))
Word64
osRenderQueueStartTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
96 :: Ptr Word64))
Word64
osRenderQueueEndTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
104 :: Ptr Word64))
Word64
gpuRenderStartTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
112 :: Ptr Word64))
Word64
gpuRenderEndTimeUs <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencyTimingsFrameReportNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
120 :: Ptr Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> LatencyTimingsFrameReportNV
LatencyTimingsFrameReportNV
Word64
presentID
Word64
inputSampleTimeUs
Word64
simStartTimeUs
Word64
simEndTimeUs
Word64
renderSubmitStartTimeUs
Word64
renderSubmitEndTimeUs
Word64
presentStartTimeUs
Word64
presentEndTimeUs
Word64
driverStartTimeUs
Word64
driverEndTimeUs
Word64
osRenderQueueStartTimeUs
Word64
osRenderQueueEndTimeUs
Word64
gpuRenderStartTimeUs
Word64
gpuRenderEndTimeUs
instance Storable LatencyTimingsFrameReportNV where
sizeOf :: LatencyTimingsFrameReportNV -> Int
sizeOf ~LatencyTimingsFrameReportNV
_ = Int
128
alignment :: LatencyTimingsFrameReportNV -> Int
alignment ~LatencyTimingsFrameReportNV
_ = Int
8
peek :: Ptr LatencyTimingsFrameReportNV -> IO LatencyTimingsFrameReportNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr LatencyTimingsFrameReportNV
-> LatencyTimingsFrameReportNV -> IO ()
poke Ptr LatencyTimingsFrameReportNV
ptr LatencyTimingsFrameReportNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr LatencyTimingsFrameReportNV
ptr LatencyTimingsFrameReportNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero LatencyTimingsFrameReportNV where
zero :: LatencyTimingsFrameReportNV
zero = Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> Word64
-> LatencyTimingsFrameReportNV
LatencyTimingsFrameReportNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero
data OutOfBandQueueTypeInfoNV = OutOfBandQueueTypeInfoNV
{
OutOfBandQueueTypeInfoNV -> OutOfBandQueueTypeNV
queueType :: OutOfBandQueueTypeNV }
deriving (Typeable, OutOfBandQueueTypeInfoNV -> OutOfBandQueueTypeInfoNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutOfBandQueueTypeInfoNV -> OutOfBandQueueTypeInfoNV -> Bool
$c/= :: OutOfBandQueueTypeInfoNV -> OutOfBandQueueTypeInfoNV -> Bool
== :: OutOfBandQueueTypeInfoNV -> OutOfBandQueueTypeInfoNV -> Bool
$c== :: OutOfBandQueueTypeInfoNV -> OutOfBandQueueTypeInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (OutOfBandQueueTypeInfoNV)
#endif
deriving instance Show OutOfBandQueueTypeInfoNV
instance ToCStruct OutOfBandQueueTypeInfoNV where
withCStruct :: forall b.
OutOfBandQueueTypeInfoNV
-> (("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO b)
-> IO b
withCStruct OutOfBandQueueTypeInfoNV
x ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p OutOfBandQueueTypeInfoNV
x (("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO b
f "pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p)
pokeCStruct :: forall b.
("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV)
-> OutOfBandQueueTypeInfoNV -> IO b -> IO b
pokeCStruct "pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p OutOfBandQueueTypeInfoNV{OutOfBandQueueTypeNV
queueType :: OutOfBandQueueTypeNV
$sel:queueType:OutOfBandQueueTypeInfoNV :: OutOfBandQueueTypeInfoNV -> OutOfBandQueueTypeNV
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_OUT_OF_BAND_QUEUE_TYPE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
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 (("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr OutOfBandQueueTypeNV)) (OutOfBandQueueTypeNV
queueType)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV) -> IO b -> IO b
pokeZeroCStruct "pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_OUT_OF_BAND_QUEUE_TYPE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
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 (("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr OutOfBandQueueTypeNV)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct OutOfBandQueueTypeInfoNV where
peekCStruct :: ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV)
-> IO OutOfBandQueueTypeInfoNV
peekCStruct "pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p = do
OutOfBandQueueTypeNV
queueType <- forall a. Storable a => Ptr a -> IO a
peek @OutOfBandQueueTypeNV (("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr OutOfBandQueueTypeNV))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ OutOfBandQueueTypeNV -> OutOfBandQueueTypeInfoNV
OutOfBandQueueTypeInfoNV
OutOfBandQueueTypeNV
queueType
instance Storable OutOfBandQueueTypeInfoNV where
sizeOf :: OutOfBandQueueTypeInfoNV -> Int
sizeOf ~OutOfBandQueueTypeInfoNV
_ = Int
24
alignment :: OutOfBandQueueTypeInfoNV -> Int
alignment ~OutOfBandQueueTypeInfoNV
_ = Int
8
peek :: ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV)
-> IO OutOfBandQueueTypeInfoNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV)
-> OutOfBandQueueTypeInfoNV -> IO ()
poke "pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
ptr OutOfBandQueueTypeInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pQueueTypeInfo" ::: Ptr OutOfBandQueueTypeInfoNV
ptr OutOfBandQueueTypeInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero OutOfBandQueueTypeInfoNV where
zero :: OutOfBandQueueTypeInfoNV
zero = OutOfBandQueueTypeNV -> OutOfBandQueueTypeInfoNV
OutOfBandQueueTypeInfoNV
forall a. Zero a => a
zero
data LatencySubmissionPresentIdNV = LatencySubmissionPresentIdNV
{
LatencySubmissionPresentIdNV -> Word64
presentID :: Word64 }
deriving (Typeable, LatencySubmissionPresentIdNV
-> LatencySubmissionPresentIdNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LatencySubmissionPresentIdNV
-> LatencySubmissionPresentIdNV -> Bool
$c/= :: LatencySubmissionPresentIdNV
-> LatencySubmissionPresentIdNV -> Bool
== :: LatencySubmissionPresentIdNV
-> LatencySubmissionPresentIdNV -> Bool
$c== :: LatencySubmissionPresentIdNV
-> LatencySubmissionPresentIdNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (LatencySubmissionPresentIdNV)
#endif
deriving instance Show LatencySubmissionPresentIdNV
instance ToCStruct LatencySubmissionPresentIdNV where
withCStruct :: forall b.
LatencySubmissionPresentIdNV
-> (Ptr LatencySubmissionPresentIdNV -> IO b) -> IO b
withCStruct LatencySubmissionPresentIdNV
x Ptr LatencySubmissionPresentIdNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr LatencySubmissionPresentIdNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr LatencySubmissionPresentIdNV
p LatencySubmissionPresentIdNV
x (Ptr LatencySubmissionPresentIdNV -> IO b
f Ptr LatencySubmissionPresentIdNV
p)
pokeCStruct :: forall b.
Ptr LatencySubmissionPresentIdNV
-> LatencySubmissionPresentIdNV -> IO b -> IO b
pokeCStruct Ptr LatencySubmissionPresentIdNV
p LatencySubmissionPresentIdNV{Word64
presentID :: Word64
$sel:presentID:LatencySubmissionPresentIdNV :: LatencySubmissionPresentIdNV -> Word64
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencySubmissionPresentIdNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_SUBMISSION_PRESENT_ID_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencySubmissionPresentIdNV
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 LatencySubmissionPresentIdNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
presentID)
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr LatencySubmissionPresentIdNV -> IO b -> IO b
pokeZeroCStruct Ptr LatencySubmissionPresentIdNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencySubmissionPresentIdNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_SUBMISSION_PRESENT_ID_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencySubmissionPresentIdNV
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 LatencySubmissionPresentIdNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (forall a. Zero a => a
zero)
IO b
f
instance FromCStruct LatencySubmissionPresentIdNV where
peekCStruct :: Ptr LatencySubmissionPresentIdNV -> IO LatencySubmissionPresentIdNV
peekCStruct Ptr LatencySubmissionPresentIdNV
p = do
Word64
presentID <- forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr LatencySubmissionPresentIdNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Word64 -> LatencySubmissionPresentIdNV
LatencySubmissionPresentIdNV
Word64
presentID
instance Storable LatencySubmissionPresentIdNV where
sizeOf :: LatencySubmissionPresentIdNV -> Int
sizeOf ~LatencySubmissionPresentIdNV
_ = Int
24
alignment :: LatencySubmissionPresentIdNV -> Int
alignment ~LatencySubmissionPresentIdNV
_ = Int
8
peek :: Ptr LatencySubmissionPresentIdNV -> IO LatencySubmissionPresentIdNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr LatencySubmissionPresentIdNV
-> LatencySubmissionPresentIdNV -> IO ()
poke Ptr LatencySubmissionPresentIdNV
ptr LatencySubmissionPresentIdNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr LatencySubmissionPresentIdNV
ptr LatencySubmissionPresentIdNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero LatencySubmissionPresentIdNV where
zero :: LatencySubmissionPresentIdNV
zero = Word64 -> LatencySubmissionPresentIdNV
LatencySubmissionPresentIdNV
forall a. Zero a => a
zero
data SwapchainLatencyCreateInfoNV = SwapchainLatencyCreateInfoNV
{
SwapchainLatencyCreateInfoNV -> Bool
latencyModeEnable :: Bool }
deriving (Typeable, SwapchainLatencyCreateInfoNV
-> SwapchainLatencyCreateInfoNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwapchainLatencyCreateInfoNV
-> SwapchainLatencyCreateInfoNV -> Bool
$c/= :: SwapchainLatencyCreateInfoNV
-> SwapchainLatencyCreateInfoNV -> Bool
== :: SwapchainLatencyCreateInfoNV
-> SwapchainLatencyCreateInfoNV -> Bool
$c== :: SwapchainLatencyCreateInfoNV
-> SwapchainLatencyCreateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SwapchainLatencyCreateInfoNV)
#endif
deriving instance Show SwapchainLatencyCreateInfoNV
instance ToCStruct SwapchainLatencyCreateInfoNV where
withCStruct :: forall b.
SwapchainLatencyCreateInfoNV
-> (Ptr SwapchainLatencyCreateInfoNV -> IO b) -> IO b
withCStruct SwapchainLatencyCreateInfoNV
x Ptr SwapchainLatencyCreateInfoNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr SwapchainLatencyCreateInfoNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SwapchainLatencyCreateInfoNV
p SwapchainLatencyCreateInfoNV
x (Ptr SwapchainLatencyCreateInfoNV -> IO b
f Ptr SwapchainLatencyCreateInfoNV
p)
pokeCStruct :: forall b.
Ptr SwapchainLatencyCreateInfoNV
-> SwapchainLatencyCreateInfoNV -> IO b -> IO b
pokeCStruct Ptr SwapchainLatencyCreateInfoNV
p SwapchainLatencyCreateInfoNV{Bool
latencyModeEnable :: Bool
$sel:latencyModeEnable:SwapchainLatencyCreateInfoNV :: SwapchainLatencyCreateInfoNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainLatencyCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_LATENCY_CREATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainLatencyCreateInfoNV
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 SwapchainLatencyCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
latencyModeEnable))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr SwapchainLatencyCreateInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr SwapchainLatencyCreateInfoNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainLatencyCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SWAPCHAIN_LATENCY_CREATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr SwapchainLatencyCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct SwapchainLatencyCreateInfoNV where
peekCStruct :: Ptr SwapchainLatencyCreateInfoNV -> IO SwapchainLatencyCreateInfoNV
peekCStruct Ptr SwapchainLatencyCreateInfoNV
p = do
Bool32
latencyModeEnable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr SwapchainLatencyCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> SwapchainLatencyCreateInfoNV
SwapchainLatencyCreateInfoNV
(Bool32 -> Bool
bool32ToBool Bool32
latencyModeEnable)
instance Storable SwapchainLatencyCreateInfoNV where
sizeOf :: SwapchainLatencyCreateInfoNV -> Int
sizeOf ~SwapchainLatencyCreateInfoNV
_ = Int
24
alignment :: SwapchainLatencyCreateInfoNV -> Int
alignment ~SwapchainLatencyCreateInfoNV
_ = Int
8
peek :: Ptr SwapchainLatencyCreateInfoNV -> IO SwapchainLatencyCreateInfoNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr SwapchainLatencyCreateInfoNV
-> SwapchainLatencyCreateInfoNV -> IO ()
poke Ptr SwapchainLatencyCreateInfoNV
ptr SwapchainLatencyCreateInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr SwapchainLatencyCreateInfoNV
ptr SwapchainLatencyCreateInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero SwapchainLatencyCreateInfoNV where
zero :: SwapchainLatencyCreateInfoNV
zero = Bool -> SwapchainLatencyCreateInfoNV
SwapchainLatencyCreateInfoNV
forall a. Zero a => a
zero
data LatencySurfaceCapabilitiesNV = LatencySurfaceCapabilitiesNV
{
LatencySurfaceCapabilitiesNV -> "timingCount" ::: Word32
presentModeCount :: Word32
,
LatencySurfaceCapabilitiesNV -> Ptr PresentModeKHR
presentModes :: Ptr PresentModeKHR
}
deriving (Typeable, LatencySurfaceCapabilitiesNV
-> LatencySurfaceCapabilitiesNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LatencySurfaceCapabilitiesNV
-> LatencySurfaceCapabilitiesNV -> Bool
$c/= :: LatencySurfaceCapabilitiesNV
-> LatencySurfaceCapabilitiesNV -> Bool
== :: LatencySurfaceCapabilitiesNV
-> LatencySurfaceCapabilitiesNV -> Bool
$c== :: LatencySurfaceCapabilitiesNV
-> LatencySurfaceCapabilitiesNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (LatencySurfaceCapabilitiesNV)
#endif
deriving instance Show LatencySurfaceCapabilitiesNV
instance ToCStruct LatencySurfaceCapabilitiesNV where
withCStruct :: forall b.
LatencySurfaceCapabilitiesNV
-> (Ptr LatencySurfaceCapabilitiesNV -> IO b) -> IO b
withCStruct LatencySurfaceCapabilitiesNV
x Ptr LatencySurfaceCapabilitiesNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr LatencySurfaceCapabilitiesNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr LatencySurfaceCapabilitiesNV
p LatencySurfaceCapabilitiesNV
x (Ptr LatencySurfaceCapabilitiesNV -> IO b
f Ptr LatencySurfaceCapabilitiesNV
p)
pokeCStruct :: forall b.
Ptr LatencySurfaceCapabilitiesNV
-> LatencySurfaceCapabilitiesNV -> IO b -> IO b
pokeCStruct Ptr LatencySurfaceCapabilitiesNV
p LatencySurfaceCapabilitiesNV{"timingCount" ::: Word32
Ptr PresentModeKHR
presentModes :: Ptr PresentModeKHR
presentModeCount :: "timingCount" ::: Word32
$sel:presentModes:LatencySurfaceCapabilitiesNV :: LatencySurfaceCapabilitiesNV -> Ptr PresentModeKHR
$sel:presentModeCount:LatencySurfaceCapabilitiesNV :: LatencySurfaceCapabilitiesNV -> "timingCount" ::: Word32
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencySurfaceCapabilitiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_SURFACE_CAPABILITIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencySurfaceCapabilitiesNV
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 LatencySurfaceCapabilitiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) ("timingCount" ::: Word32
presentModeCount)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencySurfaceCapabilitiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr PresentModeKHR))) (Ptr PresentModeKHR
presentModes)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr LatencySurfaceCapabilitiesNV -> IO b -> IO b
pokeZeroCStruct Ptr LatencySurfaceCapabilitiesNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencySurfaceCapabilitiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_LATENCY_SURFACE_CAPABILITIES_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr LatencySurfaceCapabilitiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct LatencySurfaceCapabilitiesNV where
peekCStruct :: Ptr LatencySurfaceCapabilitiesNV -> IO LatencySurfaceCapabilitiesNV
peekCStruct Ptr LatencySurfaceCapabilitiesNV
p = do
"timingCount" ::: Word32
presentModeCount <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr LatencySurfaceCapabilitiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
Ptr PresentModeKHR
pPresentModes <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr PresentModeKHR) ((Ptr LatencySurfaceCapabilitiesNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (Ptr PresentModeKHR)))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ("timingCount" ::: Word32)
-> Ptr PresentModeKHR -> LatencySurfaceCapabilitiesNV
LatencySurfaceCapabilitiesNV
"timingCount" ::: Word32
presentModeCount Ptr PresentModeKHR
pPresentModes
instance Storable LatencySurfaceCapabilitiesNV where
sizeOf :: LatencySurfaceCapabilitiesNV -> Int
sizeOf ~LatencySurfaceCapabilitiesNV
_ = Int
32
alignment :: LatencySurfaceCapabilitiesNV -> Int
alignment ~LatencySurfaceCapabilitiesNV
_ = Int
8
peek :: Ptr LatencySurfaceCapabilitiesNV -> IO LatencySurfaceCapabilitiesNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr LatencySurfaceCapabilitiesNV
-> LatencySurfaceCapabilitiesNV -> IO ()
poke Ptr LatencySurfaceCapabilitiesNV
ptr LatencySurfaceCapabilitiesNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr LatencySurfaceCapabilitiesNV
ptr LatencySurfaceCapabilitiesNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero LatencySurfaceCapabilitiesNV where
zero :: LatencySurfaceCapabilitiesNV
zero = ("timingCount" ::: Word32)
-> Ptr PresentModeKHR -> LatencySurfaceCapabilitiesNV
LatencySurfaceCapabilitiesNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
newtype LatencyMarkerNV = LatencyMarkerNV Int32
deriving newtype (LatencyMarkerNV -> LatencyMarkerNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
$c/= :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
== :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
$c== :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
Eq, Eq LatencyMarkerNV
LatencyMarkerNV -> LatencyMarkerNV -> Bool
LatencyMarkerNV -> LatencyMarkerNV -> Ordering
LatencyMarkerNV -> LatencyMarkerNV -> LatencyMarkerNV
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 :: LatencyMarkerNV -> LatencyMarkerNV -> LatencyMarkerNV
$cmin :: LatencyMarkerNV -> LatencyMarkerNV -> LatencyMarkerNV
max :: LatencyMarkerNV -> LatencyMarkerNV -> LatencyMarkerNV
$cmax :: LatencyMarkerNV -> LatencyMarkerNV -> LatencyMarkerNV
>= :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
$c>= :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
> :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
$c> :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
<= :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
$c<= :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
< :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
$c< :: LatencyMarkerNV -> LatencyMarkerNV -> Bool
compare :: LatencyMarkerNV -> LatencyMarkerNV -> Ordering
$ccompare :: LatencyMarkerNV -> LatencyMarkerNV -> Ordering
Ord, Ptr LatencyMarkerNV -> IO LatencyMarkerNV
Ptr LatencyMarkerNV -> Int -> IO LatencyMarkerNV
Ptr LatencyMarkerNV -> Int -> LatencyMarkerNV -> IO ()
Ptr LatencyMarkerNV -> LatencyMarkerNV -> IO ()
LatencyMarkerNV -> Int
forall b. Ptr b -> Int -> IO LatencyMarkerNV
forall b. Ptr b -> Int -> LatencyMarkerNV -> 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 LatencyMarkerNV -> LatencyMarkerNV -> IO ()
$cpoke :: Ptr LatencyMarkerNV -> LatencyMarkerNV -> IO ()
peek :: Ptr LatencyMarkerNV -> IO LatencyMarkerNV
$cpeek :: Ptr LatencyMarkerNV -> IO LatencyMarkerNV
pokeByteOff :: forall b. Ptr b -> Int -> LatencyMarkerNV -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> LatencyMarkerNV -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO LatencyMarkerNV
$cpeekByteOff :: forall b. Ptr b -> Int -> IO LatencyMarkerNV
pokeElemOff :: Ptr LatencyMarkerNV -> Int -> LatencyMarkerNV -> IO ()
$cpokeElemOff :: Ptr LatencyMarkerNV -> Int -> LatencyMarkerNV -> IO ()
peekElemOff :: Ptr LatencyMarkerNV -> Int -> IO LatencyMarkerNV
$cpeekElemOff :: Ptr LatencyMarkerNV -> Int -> IO LatencyMarkerNV
alignment :: LatencyMarkerNV -> Int
$calignment :: LatencyMarkerNV -> Int
sizeOf :: LatencyMarkerNV -> Int
$csizeOf :: LatencyMarkerNV -> Int
Storable, LatencyMarkerNV
forall a. a -> Zero a
zero :: LatencyMarkerNV
$czero :: LatencyMarkerNV
Zero)
pattern $bLATENCY_MARKER_SIMULATION_START_NV :: LatencyMarkerNV
$mLATENCY_MARKER_SIMULATION_START_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_SIMULATION_START_NV = LatencyMarkerNV 0
pattern $bLATENCY_MARKER_SIMULATION_END_NV :: LatencyMarkerNV
$mLATENCY_MARKER_SIMULATION_END_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_SIMULATION_END_NV = LatencyMarkerNV 1
pattern $bLATENCY_MARKER_RENDERSUBMIT_START_NV :: LatencyMarkerNV
$mLATENCY_MARKER_RENDERSUBMIT_START_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_RENDERSUBMIT_START_NV = LatencyMarkerNV 2
pattern $bLATENCY_MARKER_RENDERSUBMIT_END_NV :: LatencyMarkerNV
$mLATENCY_MARKER_RENDERSUBMIT_END_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_RENDERSUBMIT_END_NV = LatencyMarkerNV 3
pattern $bLATENCY_MARKER_PRESENT_START_NV :: LatencyMarkerNV
$mLATENCY_MARKER_PRESENT_START_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_PRESENT_START_NV = LatencyMarkerNV 4
pattern $bLATENCY_MARKER_PRESENT_END_NV :: LatencyMarkerNV
$mLATENCY_MARKER_PRESENT_END_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_PRESENT_END_NV = LatencyMarkerNV 5
pattern $bLATENCY_MARKER_INPUT_SAMPLE_NV :: LatencyMarkerNV
$mLATENCY_MARKER_INPUT_SAMPLE_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_INPUT_SAMPLE_NV = LatencyMarkerNV 6
pattern $bLATENCY_MARKER_TRIGGER_FLASH_NV :: LatencyMarkerNV
$mLATENCY_MARKER_TRIGGER_FLASH_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_TRIGGER_FLASH_NV = LatencyMarkerNV 7
pattern $bLATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_START_NV :: LatencyMarkerNV
$mLATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_START_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_START_NV = LatencyMarkerNV 8
pattern $bLATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_END_NV :: LatencyMarkerNV
$mLATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_END_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_END_NV = LatencyMarkerNV 9
pattern $bLATENCY_MARKER_OUT_OF_BAND_PRESENT_START_NV :: LatencyMarkerNV
$mLATENCY_MARKER_OUT_OF_BAND_PRESENT_START_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_OUT_OF_BAND_PRESENT_START_NV = LatencyMarkerNV 10
pattern $bLATENCY_MARKER_OUT_OF_BAND_PRESENT_END_NV :: LatencyMarkerNV
$mLATENCY_MARKER_OUT_OF_BAND_PRESENT_END_NV :: forall {r}. LatencyMarkerNV -> ((# #) -> r) -> ((# #) -> r) -> r
LATENCY_MARKER_OUT_OF_BAND_PRESENT_END_NV = LatencyMarkerNV 11
{-# COMPLETE
LATENCY_MARKER_SIMULATION_START_NV
, LATENCY_MARKER_SIMULATION_END_NV
, LATENCY_MARKER_RENDERSUBMIT_START_NV
, LATENCY_MARKER_RENDERSUBMIT_END_NV
, LATENCY_MARKER_PRESENT_START_NV
, LATENCY_MARKER_PRESENT_END_NV
, LATENCY_MARKER_INPUT_SAMPLE_NV
, LATENCY_MARKER_TRIGGER_FLASH_NV
, LATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_START_NV
, LATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_END_NV
, LATENCY_MARKER_OUT_OF_BAND_PRESENT_START_NV
, LATENCY_MARKER_OUT_OF_BAND_PRESENT_END_NV ::
LatencyMarkerNV
#-}
conNameLatencyMarkerNV :: String
conNameLatencyMarkerNV :: String
conNameLatencyMarkerNV = String
"LatencyMarkerNV"
enumPrefixLatencyMarkerNV :: String
enumPrefixLatencyMarkerNV :: String
enumPrefixLatencyMarkerNV = String
"LATENCY_MARKER_"
showTableLatencyMarkerNV :: [(LatencyMarkerNV, String)]
showTableLatencyMarkerNV :: [(LatencyMarkerNV, String)]
showTableLatencyMarkerNV =
[
( LatencyMarkerNV
LATENCY_MARKER_SIMULATION_START_NV
, String
"SIMULATION_START_NV"
)
,
( LatencyMarkerNV
LATENCY_MARKER_SIMULATION_END_NV
, String
"SIMULATION_END_NV"
)
,
( LatencyMarkerNV
LATENCY_MARKER_RENDERSUBMIT_START_NV
, String
"RENDERSUBMIT_START_NV"
)
,
( LatencyMarkerNV
LATENCY_MARKER_RENDERSUBMIT_END_NV
, String
"RENDERSUBMIT_END_NV"
)
,
( LatencyMarkerNV
LATENCY_MARKER_PRESENT_START_NV
, String
"PRESENT_START_NV"
)
, (LatencyMarkerNV
LATENCY_MARKER_PRESENT_END_NV, String
"PRESENT_END_NV")
, (LatencyMarkerNV
LATENCY_MARKER_INPUT_SAMPLE_NV, String
"INPUT_SAMPLE_NV")
,
( LatencyMarkerNV
LATENCY_MARKER_TRIGGER_FLASH_NV
, String
"TRIGGER_FLASH_NV"
)
,
( LatencyMarkerNV
LATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_START_NV
, String
"OUT_OF_BAND_RENDERSUBMIT_START_NV"
)
,
( LatencyMarkerNV
LATENCY_MARKER_OUT_OF_BAND_RENDERSUBMIT_END_NV
, String
"OUT_OF_BAND_RENDERSUBMIT_END_NV"
)
,
( LatencyMarkerNV
LATENCY_MARKER_OUT_OF_BAND_PRESENT_START_NV
, String
"OUT_OF_BAND_PRESENT_START_NV"
)
,
( LatencyMarkerNV
LATENCY_MARKER_OUT_OF_BAND_PRESENT_END_NV
, String
"OUT_OF_BAND_PRESENT_END_NV"
)
]
instance Show LatencyMarkerNV where
showsPrec :: Int -> LatencyMarkerNV -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixLatencyMarkerNV
[(LatencyMarkerNV, String)]
showTableLatencyMarkerNV
String
conNameLatencyMarkerNV
(\(LatencyMarkerNV Int32
x) -> Int32
x)
(forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)
instance Read LatencyMarkerNV where
readPrec :: ReadPrec LatencyMarkerNV
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixLatencyMarkerNV
[(LatencyMarkerNV, String)]
showTableLatencyMarkerNV
String
conNameLatencyMarkerNV
Int32 -> LatencyMarkerNV
LatencyMarkerNV
newtype OutOfBandQueueTypeNV = OutOfBandQueueTypeNV Int32
deriving newtype (OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
$c/= :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
== :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
$c== :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
Eq, Eq OutOfBandQueueTypeNV
OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Ordering
OutOfBandQueueTypeNV
-> OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV
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 :: OutOfBandQueueTypeNV
-> OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV
$cmin :: OutOfBandQueueTypeNV
-> OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV
max :: OutOfBandQueueTypeNV
-> OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV
$cmax :: OutOfBandQueueTypeNV
-> OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV
>= :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
$c>= :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
> :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
$c> :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
<= :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
$c<= :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
< :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
$c< :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Bool
compare :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Ordering
$ccompare :: OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> Ordering
Ord, Ptr OutOfBandQueueTypeNV -> IO OutOfBandQueueTypeNV
Ptr OutOfBandQueueTypeNV -> Int -> IO OutOfBandQueueTypeNV
Ptr OutOfBandQueueTypeNV -> Int -> OutOfBandQueueTypeNV -> IO ()
Ptr OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> IO ()
OutOfBandQueueTypeNV -> Int
forall b. Ptr b -> Int -> IO OutOfBandQueueTypeNV
forall b. Ptr b -> Int -> OutOfBandQueueTypeNV -> 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 OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> IO ()
$cpoke :: Ptr OutOfBandQueueTypeNV -> OutOfBandQueueTypeNV -> IO ()
peek :: Ptr OutOfBandQueueTypeNV -> IO OutOfBandQueueTypeNV
$cpeek :: Ptr OutOfBandQueueTypeNV -> IO OutOfBandQueueTypeNV
pokeByteOff :: forall b. Ptr b -> Int -> OutOfBandQueueTypeNV -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> OutOfBandQueueTypeNV -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO OutOfBandQueueTypeNV
$cpeekByteOff :: forall b. Ptr b -> Int -> IO OutOfBandQueueTypeNV
pokeElemOff :: Ptr OutOfBandQueueTypeNV -> Int -> OutOfBandQueueTypeNV -> IO ()
$cpokeElemOff :: Ptr OutOfBandQueueTypeNV -> Int -> OutOfBandQueueTypeNV -> IO ()
peekElemOff :: Ptr OutOfBandQueueTypeNV -> Int -> IO OutOfBandQueueTypeNV
$cpeekElemOff :: Ptr OutOfBandQueueTypeNV -> Int -> IO OutOfBandQueueTypeNV
alignment :: OutOfBandQueueTypeNV -> Int
$calignment :: OutOfBandQueueTypeNV -> Int
sizeOf :: OutOfBandQueueTypeNV -> Int
$csizeOf :: OutOfBandQueueTypeNV -> Int
Storable, OutOfBandQueueTypeNV
forall a. a -> Zero a
zero :: OutOfBandQueueTypeNV
$czero :: OutOfBandQueueTypeNV
Zero)
pattern $bOUT_OF_BAND_QUEUE_TYPE_RENDER_NV :: OutOfBandQueueTypeNV
$mOUT_OF_BAND_QUEUE_TYPE_RENDER_NV :: forall {r}.
OutOfBandQueueTypeNV -> ((# #) -> r) -> ((# #) -> r) -> r
OUT_OF_BAND_QUEUE_TYPE_RENDER_NV = OutOfBandQueueTypeNV 0
pattern $bOUT_OF_BAND_QUEUE_TYPE_PRESENT_NV :: OutOfBandQueueTypeNV
$mOUT_OF_BAND_QUEUE_TYPE_PRESENT_NV :: forall {r}.
OutOfBandQueueTypeNV -> ((# #) -> r) -> ((# #) -> r) -> r
OUT_OF_BAND_QUEUE_TYPE_PRESENT_NV = OutOfBandQueueTypeNV 1
{-# COMPLETE
OUT_OF_BAND_QUEUE_TYPE_RENDER_NV
, OUT_OF_BAND_QUEUE_TYPE_PRESENT_NV ::
OutOfBandQueueTypeNV
#-}
conNameOutOfBandQueueTypeNV :: String
conNameOutOfBandQueueTypeNV :: String
conNameOutOfBandQueueTypeNV = String
"OutOfBandQueueTypeNV"
enumPrefixOutOfBandQueueTypeNV :: String
enumPrefixOutOfBandQueueTypeNV :: String
enumPrefixOutOfBandQueueTypeNV = String
"OUT_OF_BAND_QUEUE_TYPE_"
showTableOutOfBandQueueTypeNV :: [(OutOfBandQueueTypeNV, String)]
showTableOutOfBandQueueTypeNV :: [(OutOfBandQueueTypeNV, String)]
showTableOutOfBandQueueTypeNV =
[
( OutOfBandQueueTypeNV
OUT_OF_BAND_QUEUE_TYPE_RENDER_NV
, String
"RENDER_NV"
)
,
( OutOfBandQueueTypeNV
OUT_OF_BAND_QUEUE_TYPE_PRESENT_NV
, String
"PRESENT_NV"
)
]
instance Show OutOfBandQueueTypeNV where
showsPrec :: Int -> OutOfBandQueueTypeNV -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixOutOfBandQueueTypeNV
[(OutOfBandQueueTypeNV, String)]
showTableOutOfBandQueueTypeNV
String
conNameOutOfBandQueueTypeNV
(\(OutOfBandQueueTypeNV Int32
x) -> Int32
x)
(forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)
instance Read OutOfBandQueueTypeNV where
readPrec :: ReadPrec OutOfBandQueueTypeNV
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixOutOfBandQueueTypeNV
[(OutOfBandQueueTypeNV, String)]
showTableOutOfBandQueueTypeNV
String
conNameOutOfBandQueueTypeNV
Int32 -> OutOfBandQueueTypeNV
OutOfBandQueueTypeNV
type NV_LOW_LATENCY_2_SPEC_VERSION = 1
pattern NV_LOW_LATENCY_2_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_LOW_LATENCY_2_SPEC_VERSION :: forall a. Integral a => a
$mNV_LOW_LATENCY_2_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_LOW_LATENCY_2_SPEC_VERSION = 1
type NV_LOW_LATENCY_2_EXTENSION_NAME = "VK_NV_low_latency2"
pattern NV_LOW_LATENCY_2_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_LOW_LATENCY_2_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_LOW_LATENCY_2_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_LOW_LATENCY_2_EXTENSION_NAME = "VK_NV_low_latency2"