{-# language CPP #-}
-- | = Name
--
-- VK_EXT_calibrated_timestamps - device extension
--
-- == VK_EXT_calibrated_timestamps
--
-- [__Name String__]
--     @VK_EXT_calibrated_timestamps@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     185
--
-- [__Revision__]
--     2
--
-- [__Ratification Status__]
--     Not ratified
--
-- [__Extension and Version Dependencies__]
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_get_physical_device_properties2 VK_KHR_get_physical_device_properties2>
--     or
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#versions-1.1 Version 1.1>
--
-- [__Contact__]
--
--     -   Daniel Rakos
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_calibrated_timestamps] @drakos-amd%0A*Here describe the issue or question you have about the VK_EXT_calibrated_timestamps extension* >
--
-- [__Extension Proposal__]
--     <https://github.com/KhronosGroup/Vulkan-Docs/tree/main/proposals/VK_EXT_calibrated_timestamps.adoc VK_EXT_calibrated_timestamps>
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2018-10-04
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Matthaeus G. Chajdas, AMD
--
--     -   Alan Harrison, AMD
--
--     -   Derrick Owens, AMD
--
--     -   Daniel Rakos, AMD
--
--     -   Faith Ekstrand, Intel
--
--     -   Keith Packard, Valve
--
-- == Description
--
-- This extension provides an interface to query calibrated timestamps
-- obtained quasi simultaneously from two time domains.
--
-- == New Commands
--
-- -   'getCalibratedTimestampsEXT'
--
-- -   'getPhysicalDeviceCalibrateableTimeDomainsEXT'
--
-- == New Structures
--
-- -   'CalibratedTimestampInfoEXT'
--
-- == New Enums
--
-- -   'TimeDomainEXT'
--
-- == New Enum Constants
--
-- -   'EXT_CALIBRATED_TIMESTAMPS_EXTENSION_NAME'
--
-- -   'EXT_CALIBRATED_TIMESTAMPS_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_CALIBRATED_TIMESTAMP_INFO_EXT'
--
-- == Version History
--
-- -   Revision 2, 2021-03-16 (Lionel Landwerlin)
--
--     -   Specify requirement on device timestamps
--
-- -   Revision 1, 2018-10-04 (Daniel Rakos)
--
--     -   Internal revisions.
--
-- == See Also
--
-- 'CalibratedTimestampInfoEXT', 'TimeDomainEXT',
-- 'getCalibratedTimestampsEXT',
-- 'getPhysicalDeviceCalibrateableTimeDomainsEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_calibrated_timestamps Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_calibrated_timestamps  ( getPhysicalDeviceCalibrateableTimeDomainsEXT
                                                       , getCalibratedTimestampsEXT
                                                       , CalibratedTimestampInfoEXT(..)
                                                       , TimeDomainEXT( TIME_DOMAIN_DEVICE_EXT
                                                                      , TIME_DOMAIN_CLOCK_MONOTONIC_EXT
                                                                      , TIME_DOMAIN_CLOCK_MONOTONIC_RAW_EXT
                                                                      , TIME_DOMAIN_QUERY_PERFORMANCE_COUNTER_EXT
                                                                      , ..
                                                                      )
                                                       , EXT_CALIBRATED_TIMESTAMPS_SPEC_VERSION
                                                       , pattern EXT_CALIBRATED_TIMESTAMPS_SPEC_VERSION
                                                       , EXT_CALIBRATED_TIMESTAMPS_EXTENSION_NAME
                                                       , pattern EXT_CALIBRATED_TIMESTAMPS_EXTENSION_NAME
                                                       ) 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 Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
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 Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkGetCalibratedTimestampsEXT))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceCalibrateableTimeDomainsEXT))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (PhysicalDevice(PhysicalDevice))
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_CALIBRATED_TIMESTAMP_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceCalibrateableTimeDomainsEXT
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result) -> Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result

-- | vkGetPhysicalDeviceCalibrateableTimeDomainsEXT - Query calibrateable
-- time domains
--
-- = Description
--
-- If @pTimeDomains@ is @NULL@, then the number of calibrateable time
-- domains supported for the given @physicalDevice@ is returned in
-- @pTimeDomainCount@. Otherwise, @pTimeDomainCount@ /must/ point to a
-- variable set by the user to the number of elements in the @pTimeDomains@
-- array, and on return the variable is overwritten with the number of
-- values actually written to @pTimeDomains@. If the value of
-- @pTimeDomainCount@ is less than the number of calibrateable time domains
-- supported, at most @pTimeDomainCount@ values will be written to
-- @pTimeDomains@, and 'Vulkan.Core10.Enums.Result.INCOMPLETE' will be
-- returned instead of 'Vulkan.Core10.Enums.Result.SUCCESS', to indicate
-- that not all the available time domains were returned.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkGetPhysicalDeviceCalibrateableTimeDomainsEXT-physicalDevice-parameter#
--     @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   #VUID-vkGetPhysicalDeviceCalibrateableTimeDomainsEXT-pTimeDomainCount-parameter#
--     @pTimeDomainCount@ /must/ be a valid pointer to a @uint32_t@ value
--
-- -   #VUID-vkGetPhysicalDeviceCalibrateableTimeDomainsEXT-pTimeDomains-parameter#
--     If the value referenced by @pTimeDomainCount@ is not @0@, and
--     @pTimeDomains@ is not @NULL@, @pTimeDomains@ /must/ be a valid
--     pointer to an array of @pTimeDomainCount@ 'TimeDomainEXT' values
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.INCOMPLETE'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_calibrated_timestamps VK_EXT_calibrated_timestamps>,
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'TimeDomainEXT'
getPhysicalDeviceCalibrateableTimeDomainsEXT :: forall io
                                              . (MonadIO io)
                                             => -- | @physicalDevice@ is the physical device from which to query the set of
                                                -- calibrateable time domains.
                                                PhysicalDevice
                                             -> io (Result, ("timeDomains" ::: Vector TimeDomainEXT))
getPhysicalDeviceCalibrateableTimeDomainsEXT :: forall (io :: * -> *).
MonadIO io =>
PhysicalDevice
-> io (Result, "timeDomains" ::: Vector TimeDomainEXT)
getPhysicalDeviceCalibrateableTimeDomainsEXT PhysicalDevice
physicalDevice = IO (Result, "timeDomains" ::: Vector TimeDomainEXT)
-> io (Result, "timeDomains" ::: Vector TimeDomainEXT)
forall a. IO a -> io a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "timeDomains" ::: Vector TimeDomainEXT)
 -> io (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> (ContT
      (Result, "timeDomains" ::: Vector TimeDomainEXT)
      IO
      (Result, "timeDomains" ::: Vector TimeDomainEXT)
    -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
     IO
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
-> io (Result, "timeDomains" ::: Vector TimeDomainEXT)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "timeDomains" ::: Vector TimeDomainEXT)
  IO
  (Result, "timeDomains" ::: Vector TimeDomainEXT)
-> IO (Result, "timeDomains" ::: Vector TimeDomainEXT)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "timeDomains" ::: Vector TimeDomainEXT)
   IO
   (Result, "timeDomains" ::: Vector TimeDomainEXT)
 -> io (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
     IO
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
-> io (Result, "timeDomains" ::: Vector TimeDomainEXT)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceCalibrateableTimeDomainsEXTPtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result)
vkGetPhysicalDeviceCalibrateableTimeDomainsEXTPtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result)
pVkGetPhysicalDeviceCalibrateableTimeDomainsEXT (case PhysicalDevice
physicalDevice of PhysicalDevice{InstanceCmds
instanceCmds :: InstanceCmds
$sel:instanceCmds:PhysicalDevice :: PhysicalDevice -> InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  IO ()
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO ()
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO ())
-> IO ()
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result)
vkGetPhysicalDeviceCalibrateableTimeDomainsEXTPtr FunPtr
  (Ptr PhysicalDevice_T
   -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result)
-> FunPtr
     (Ptr PhysicalDevice_T
      -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetPhysicalDeviceCalibrateableTimeDomainsEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceCalibrateableTimeDomainsEXT' :: Ptr PhysicalDevice_T
-> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result
vkGetPhysicalDeviceCalibrateableTimeDomainsEXT' = FunPtr
  (Ptr PhysicalDevice_T
   -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result)
-> Ptr PhysicalDevice_T
-> Ptr Word32
-> Ptr TimeDomainEXT
-> IO Result
mkVkGetPhysicalDeviceCalibrateableTimeDomainsEXT FunPtr
  (Ptr PhysicalDevice_T
   -> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result)
vkGetPhysicalDeviceCalibrateableTimeDomainsEXTPtr
  let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
  Ptr Word32
pPTimeDomainCount <- ((Ptr Word32
  -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
 -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT) IO (Ptr Word32)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word32
   -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
  -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
 -> ContT
      (Result, "timeDomains" ::: Vector TimeDomainEXT) IO (Ptr Word32))
-> ((Ptr Word32
     -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
    -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT) IO (Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Word32)
-> (Ptr Word32 -> IO ())
-> (Ptr Word32
    -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> IO (Result, "timeDomains" ::: Vector TimeDomainEXT)
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) Ptr Word32 -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Result
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT
      (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Result)
-> IO Result
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDeviceCalibrateableTimeDomainsEXT" (Ptr PhysicalDevice_T
-> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result
vkGetPhysicalDeviceCalibrateableTimeDomainsEXT'
                                                                                   Ptr PhysicalDevice_T
physicalDevice'
                                                                                   (Ptr Word32
pPTimeDomainCount)
                                                                                   (Ptr TimeDomainEXT
forall a. Ptr a
nullPtr))
  IO ()
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO ()
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO ())
-> IO ()
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Word32
pTimeDomainCount <- IO Word32
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Word32
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Word32)
-> IO Word32
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Word32
forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word32 Ptr Word32
pPTimeDomainCount
  Ptr TimeDomainEXT
pPTimeDomains <- ((Ptr TimeDomainEXT
  -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
 -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
     IO
     (Ptr TimeDomainEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr TimeDomainEXT
   -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
  -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
 -> ContT
      (Result, "timeDomains" ::: Vector TimeDomainEXT)
      IO
      (Ptr TimeDomainEXT))
-> ((Ptr TimeDomainEXT
     -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
    -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
     IO
     (Ptr TimeDomainEXT)
forall a b. (a -> b) -> a -> b
$ IO (Ptr TimeDomainEXT)
-> (Ptr TimeDomainEXT -> IO ())
-> (Ptr TimeDomainEXT
    -> IO (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> IO (Result, "timeDomains" ::: Vector TimeDomainEXT)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @TimeDomainEXT ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pTimeDomainCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
4)) Ptr TimeDomainEXT -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r' <- IO Result
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Result
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT
      (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Result)
-> IO Result
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPhysicalDeviceCalibrateableTimeDomainsEXT" (Ptr PhysicalDevice_T
-> Ptr Word32 -> Ptr TimeDomainEXT -> IO Result
vkGetPhysicalDeviceCalibrateableTimeDomainsEXT'
                                                                                    Ptr PhysicalDevice_T
physicalDevice'
                                                                                    (Ptr Word32
pPTimeDomainCount)
                                                                                    (Ptr TimeDomainEXT
pPTimeDomains))
  IO ()
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO ()
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO ())
-> IO ()
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
  Word32
pTimeDomainCount' <- IO Word32
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Word32
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Word32)
-> IO Word32
-> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO Word32
forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word32 Ptr Word32
pPTimeDomainCount
  "timeDomains" ::: Vector TimeDomainEXT
pTimeDomains' <- IO ("timeDomains" ::: Vector TimeDomainEXT)
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
     IO
     ("timeDomains" ::: Vector TimeDomainEXT)
forall (m :: * -> *) a.
Monad m =>
m a -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("timeDomains" ::: Vector TimeDomainEXT)
 -> ContT
      (Result, "timeDomains" ::: Vector TimeDomainEXT)
      IO
      ("timeDomains" ::: Vector TimeDomainEXT))
-> IO ("timeDomains" ::: Vector TimeDomainEXT)
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
     IO
     ("timeDomains" ::: Vector TimeDomainEXT)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO TimeDomainEXT)
-> IO ("timeDomains" ::: Vector TimeDomainEXT)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pTimeDomainCount')) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @TimeDomainEXT ((Ptr TimeDomainEXT
pPTimeDomains Ptr TimeDomainEXT -> Int -> Ptr TimeDomainEXT
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr TimeDomainEXT)))
  (Result, "timeDomains" ::: Vector TimeDomainEXT)
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
     IO
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
forall a.
a -> ContT (Result, "timeDomains" ::: Vector TimeDomainEXT) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "timeDomains" ::: Vector TimeDomainEXT)
 -> ContT
      (Result, "timeDomains" ::: Vector TimeDomainEXT)
      IO
      (Result, "timeDomains" ::: Vector TimeDomainEXT))
-> (Result, "timeDomains" ::: Vector TimeDomainEXT)
-> ContT
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
     IO
     (Result, "timeDomains" ::: Vector TimeDomainEXT)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "timeDomains" ::: Vector TimeDomainEXT
pTimeDomains')


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetCalibratedTimestampsEXT
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr CalibratedTimestampInfoEXT -> Ptr Word64 -> Ptr Word64 -> IO Result) -> Ptr Device_T -> Word32 -> Ptr CalibratedTimestampInfoEXT -> Ptr Word64 -> Ptr Word64 -> IO Result

-- | vkGetCalibratedTimestampsEXT - Query calibrated timestamps
--
-- = Description
--
-- Note
--
-- The maximum deviation /may/ vary between calls to
-- 'getCalibratedTimestampsEXT' even for the same set of time domains due
-- to implementation and platform specific reasons. It is the application’s
-- responsibility to assess whether the returned maximum deviation makes
-- the timestamp values suitable for any particular purpose and /can/
-- choose to re-issue the timestamp calibration call pursuing a lower
-- deviation value.
--
-- Calibrated timestamp values /can/ be extrapolated to estimate future
-- coinciding timestamp values, however, depending on the nature of the
-- time domains and other properties of the platform extrapolating values
-- over a sufficiently long period of time /may/ no longer be accurate
-- enough to fit any particular purpose, so applications are expected to
-- re-calibrate the timestamps on a regular basis.
--
-- == Valid Usage
--
-- -   #VUID-vkGetCalibratedTimestampsEXT-timeDomain-09246# The
--     @timeDomain@ value of each 'CalibratedTimestampInfoEXT' in
--     @pTimestampInfos@ /must/ be unique
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkGetCalibratedTimestampsEXT-device-parameter# @device@ /must/
--     be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkGetCalibratedTimestampsEXT-pTimestampInfos-parameter#
--     @pTimestampInfos@ /must/ be a valid pointer to an array of
--     @timestampCount@ valid 'CalibratedTimestampInfoEXT' structures
--
-- -   #VUID-vkGetCalibratedTimestampsEXT-pTimestamps-parameter#
--     @pTimestamps@ /must/ be a valid pointer to an array of
--     @timestampCount@ @uint64_t@ values
--
-- -   #VUID-vkGetCalibratedTimestampsEXT-pMaxDeviation-parameter#
--     @pMaxDeviation@ /must/ be a valid pointer to a @uint64_t@ value
--
-- -   #VUID-vkGetCalibratedTimestampsEXT-timestampCount-arraylength#
--     @timestampCount@ /must/ be greater than @0@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_calibrated_timestamps VK_EXT_calibrated_timestamps>,
-- 'CalibratedTimestampInfoEXT', 'Vulkan.Core10.Handles.Device'
getCalibratedTimestampsEXT :: forall io
                            . (MonadIO io)
                           => -- | @device@ is the logical device used to perform the query.
                              Device
                           -> -- | @pTimestampInfos@ is a pointer to an array of @timestampCount@
                              -- 'CalibratedTimestampInfoEXT' structures, describing the time domains the
                              -- calibrated timestamps should be captured from.
                              ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT)
                           -> io (("timestamps" ::: Vector Word64), ("maxDeviation" ::: Word64))
getCalibratedTimestampsEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT)
-> io ("timestamps" ::: Vector Word64, Word64)
getCalibratedTimestampsEXT Device
device "timestampInfos" ::: Vector CalibratedTimestampInfoEXT
timestampInfos = IO ("timestamps" ::: Vector Word64, Word64)
-> io ("timestamps" ::: Vector Word64, Word64)
forall a. IO a -> io a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("timestamps" ::: Vector Word64, Word64)
 -> io ("timestamps" ::: Vector Word64, Word64))
-> (ContT
      ("timestamps" ::: Vector Word64, Word64)
      IO
      ("timestamps" ::: Vector Word64, Word64)
    -> IO ("timestamps" ::: Vector Word64, Word64))
-> ContT
     ("timestamps" ::: Vector Word64, Word64)
     IO
     ("timestamps" ::: Vector Word64, Word64)
-> io ("timestamps" ::: Vector Word64, Word64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  ("timestamps" ::: Vector Word64, Word64)
  IO
  ("timestamps" ::: Vector Word64, Word64)
-> IO ("timestamps" ::: Vector Word64, Word64)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   ("timestamps" ::: Vector Word64, Word64)
   IO
   ("timestamps" ::: Vector Word64, Word64)
 -> io ("timestamps" ::: Vector Word64, Word64))
-> ContT
     ("timestamps" ::: Vector Word64, Word64)
     IO
     ("timestamps" ::: Vector Word64, Word64)
-> io ("timestamps" ::: Vector Word64, Word64)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetCalibratedTimestampsEXTPtr :: FunPtr
  (Ptr Device_T
   -> Word32
   -> Ptr CalibratedTimestampInfoEXT
   -> Ptr Word64
   -> Ptr Word64
   -> IO Result)
vkGetCalibratedTimestampsEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Word32
      -> Ptr CalibratedTimestampInfoEXT
      -> Ptr Word64
      -> Ptr Word64
      -> IO Result)
pVkGetCalibratedTimestampsEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT ("timestamps" ::: Vector Word64, Word64) IO ()
forall (m :: * -> *) a.
Monad m =>
m a -> ContT ("timestamps" ::: Vector Word64, Word64) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("timestamps" ::: Vector Word64, Word64) IO ())
-> IO () -> ContT ("timestamps" ::: Vector Word64, Word64) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Word32
   -> Ptr CalibratedTimestampInfoEXT
   -> Ptr Word64
   -> Ptr Word64
   -> IO Result)
vkGetCalibratedTimestampsEXTPtr FunPtr
  (Ptr Device_T
   -> Word32
   -> Ptr CalibratedTimestampInfoEXT
   -> Ptr Word64
   -> Ptr Word64
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> Word32
      -> Ptr CalibratedTimestampInfoEXT
      -> Ptr Word64
      -> Ptr Word64
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Word32
   -> Ptr CalibratedTimestampInfoEXT
   -> Ptr Word64
   -> Ptr Word64
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetCalibratedTimestampsEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetCalibratedTimestampsEXT' :: Ptr Device_T
-> Word32
-> Ptr CalibratedTimestampInfoEXT
-> Ptr Word64
-> Ptr Word64
-> IO Result
vkGetCalibratedTimestampsEXT' = FunPtr
  (Ptr Device_T
   -> Word32
   -> Ptr CalibratedTimestampInfoEXT
   -> Ptr Word64
   -> Ptr Word64
   -> IO Result)
-> Ptr Device_T
-> Word32
-> Ptr CalibratedTimestampInfoEXT
-> Ptr Word64
-> Ptr Word64
-> IO Result
mkVkGetCalibratedTimestampsEXT FunPtr
  (Ptr Device_T
   -> Word32
   -> Ptr CalibratedTimestampInfoEXT
   -> Ptr Word64
   -> Ptr Word64
   -> IO Result)
vkGetCalibratedTimestampsEXTPtr
  Ptr CalibratedTimestampInfoEXT
pPTimestampInfos <- ((Ptr CalibratedTimestampInfoEXT
  -> IO ("timestamps" ::: Vector Word64, Word64))
 -> IO ("timestamps" ::: Vector Word64, Word64))
-> ContT
     ("timestamps" ::: Vector Word64, Word64)
     IO
     (Ptr CalibratedTimestampInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CalibratedTimestampInfoEXT
   -> IO ("timestamps" ::: Vector Word64, Word64))
  -> IO ("timestamps" ::: Vector Word64, Word64))
 -> ContT
      ("timestamps" ::: Vector Word64, Word64)
      IO
      (Ptr CalibratedTimestampInfoEXT))
-> ((Ptr CalibratedTimestampInfoEXT
     -> IO ("timestamps" ::: Vector Word64, Word64))
    -> IO ("timestamps" ::: Vector Word64, Word64))
-> ContT
     ("timestamps" ::: Vector Word64, Word64)
     IO
     (Ptr CalibratedTimestampInfoEXT)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @CalibratedTimestampInfoEXT ((("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT
timestampInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
24)
  IO () -> ContT ("timestamps" ::: Vector Word64, Word64) IO ()
forall (m :: * -> *) a.
Monad m =>
m a -> ContT ("timestamps" ::: Vector Word64, Word64) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("timestamps" ::: Vector Word64, Word64) IO ())
-> IO () -> ContT ("timestamps" ::: Vector Word64, Word64) IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> CalibratedTimestampInfoEXT -> IO ())
-> ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT)
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i CalibratedTimestampInfoEXT
e -> Ptr CalibratedTimestampInfoEXT
-> CalibratedTimestampInfoEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CalibratedTimestampInfoEXT
pPTimestampInfos Ptr CalibratedTimestampInfoEXT
-> Int -> Ptr CalibratedTimestampInfoEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr CalibratedTimestampInfoEXT) (CalibratedTimestampInfoEXT
e)) ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT
timestampInfos)
  Ptr Word64
pPTimestamps <- ((Ptr Word64 -> IO ("timestamps" ::: Vector Word64, Word64))
 -> IO ("timestamps" ::: Vector Word64, Word64))
-> ContT ("timestamps" ::: Vector Word64, Word64) IO (Ptr Word64)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word64 -> IO ("timestamps" ::: Vector Word64, Word64))
  -> IO ("timestamps" ::: Vector Word64, Word64))
 -> ContT ("timestamps" ::: Vector Word64, Word64) IO (Ptr Word64))
-> ((Ptr Word64 -> IO ("timestamps" ::: Vector Word64, Word64))
    -> IO ("timestamps" ::: Vector Word64, Word64))
-> ContT ("timestamps" ::: Vector Word64, Word64) IO (Ptr Word64)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Word64)
-> (Ptr Word64 -> IO ())
-> (Ptr Word64 -> IO ("timestamps" ::: Vector Word64, Word64))
-> IO ("timestamps" ::: Vector Word64, Word64)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Word64 ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length (("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int)
-> ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int
forall a b. (a -> b) -> a -> b
$ ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT
timestampInfos)) :: Word32))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8)) Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
free
  Ptr Word64
pPMaxDeviation <- ((Ptr Word64 -> IO ("timestamps" ::: Vector Word64, Word64))
 -> IO ("timestamps" ::: Vector Word64, Word64))
-> ContT ("timestamps" ::: Vector Word64, Word64) IO (Ptr Word64)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Word64 -> IO ("timestamps" ::: Vector Word64, Word64))
  -> IO ("timestamps" ::: Vector Word64, Word64))
 -> ContT ("timestamps" ::: Vector Word64, Word64) IO (Ptr Word64))
-> ((Ptr Word64 -> IO ("timestamps" ::: Vector Word64, Word64))
    -> IO ("timestamps" ::: Vector Word64, Word64))
-> ContT ("timestamps" ::: Vector Word64, Word64) IO (Ptr Word64)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Word64)
-> (Ptr Word64 -> IO ())
-> (Ptr Word64 -> IO ("timestamps" ::: Vector Word64, Word64))
-> IO ("timestamps" ::: Vector Word64, Word64)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @Word64 Int
8) Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT ("timestamps" ::: Vector Word64, Word64) IO Result
forall (m :: * -> *) a.
Monad m =>
m a -> ContT ("timestamps" ::: Vector Word64, Word64) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT ("timestamps" ::: Vector Word64, Word64) IO Result)
-> IO Result
-> ContT ("timestamps" ::: Vector Word64, Word64) IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetCalibratedTimestampsEXT" (Ptr Device_T
-> Word32
-> Ptr CalibratedTimestampInfoEXT
-> Ptr Word64
-> Ptr Word64
-> IO Result
vkGetCalibratedTimestampsEXT'
                                                                 (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                 ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length (("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int)
-> ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int
forall a b. (a -> b) -> a -> b
$ ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT
timestampInfos)) :: Word32))
                                                                 (Ptr CalibratedTimestampInfoEXT
pPTimestampInfos)
                                                                 (Ptr Word64
pPTimestamps)
                                                                 (Ptr Word64
pPMaxDeviation))
  IO () -> ContT ("timestamps" ::: Vector Word64, Word64) IO ()
forall (m :: * -> *) a.
Monad m =>
m a -> ContT ("timestamps" ::: Vector Word64, Word64) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("timestamps" ::: Vector Word64, Word64) IO ())
-> IO () -> ContT ("timestamps" ::: Vector Word64, Word64) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  "timestamps" ::: Vector Word64
pTimestamps <- IO ("timestamps" ::: Vector Word64)
-> ContT
     ("timestamps" ::: Vector Word64, Word64)
     IO
     ("timestamps" ::: Vector Word64)
forall (m :: * -> *) a.
Monad m =>
m a -> ContT ("timestamps" ::: Vector Word64, Word64) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("timestamps" ::: Vector Word64)
 -> ContT
      ("timestamps" ::: Vector Word64, Word64)
      IO
      ("timestamps" ::: Vector Word64))
-> IO ("timestamps" ::: Vector Word64)
-> ContT
     ("timestamps" ::: Vector Word64, Word64)
     IO
     ("timestamps" ::: Vector Word64)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> IO Word64) -> IO ("timestamps" ::: Vector Word64)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length (("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int)
-> ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT) -> Int
forall a b. (a -> b) -> a -> b
$ ("timestampInfos" ::: Vector CalibratedTimestampInfoEXT
timestampInfos)) :: Word32))) (\Int
i -> forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr Word64
pPTimestamps Ptr Word64 -> Int -> Ptr Word64
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word64)))
  Word64
pMaxDeviation <- IO Word64
-> ContT ("timestamps" ::: Vector Word64, Word64) IO Word64
forall (m :: * -> *) a.
Monad m =>
m a -> ContT ("timestamps" ::: Vector Word64, Word64) m a
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word64
 -> ContT ("timestamps" ::: Vector Word64, Word64) IO Word64)
-> IO Word64
-> ContT ("timestamps" ::: Vector Word64, Word64) IO Word64
forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @Word64 Ptr Word64
pPMaxDeviation
  ("timestamps" ::: Vector Word64, Word64)
-> ContT
     ("timestamps" ::: Vector Word64, Word64)
     IO
     ("timestamps" ::: Vector Word64, Word64)
forall a. a -> ContT ("timestamps" ::: Vector Word64, Word64) IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("timestamps" ::: Vector Word64, Word64)
 -> ContT
      ("timestamps" ::: Vector Word64, Word64)
      IO
      ("timestamps" ::: Vector Word64, Word64))
-> ("timestamps" ::: Vector Word64, Word64)
-> ContT
     ("timestamps" ::: Vector Word64, Word64)
     IO
     ("timestamps" ::: Vector Word64, Word64)
forall a b. (a -> b) -> a -> b
$ ("timestamps" ::: Vector Word64
pTimestamps, Word64
pMaxDeviation)


-- | VkCalibratedTimestampInfoEXT - Structure specifying the input parameters
-- of a calibrated timestamp query
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_calibrated_timestamps VK_EXT_calibrated_timestamps>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'TimeDomainEXT',
-- 'getCalibratedTimestampsEXT'
data CalibratedTimestampInfoEXT = CalibratedTimestampInfoEXT
  { -- | @timeDomain@ is a 'TimeDomainEXT' value specifying the time domain from
    -- which the calibrated timestamp value should be returned.
    --
    -- #VUID-VkCalibratedTimestampInfoEXT-timeDomain-02354# @timeDomain@ /must/
    -- be one of the 'TimeDomainEXT' values returned by
    -- 'getPhysicalDeviceCalibrateableTimeDomainsEXT'
    --
    -- #VUID-VkCalibratedTimestampInfoEXT-timeDomain-parameter# @timeDomain@
    -- /must/ be a valid 'TimeDomainEXT' value
    CalibratedTimestampInfoEXT -> TimeDomainEXT
timeDomain :: TimeDomainEXT }
  deriving (Typeable, CalibratedTimestampInfoEXT -> CalibratedTimestampInfoEXT -> Bool
(CalibratedTimestampInfoEXT -> CalibratedTimestampInfoEXT -> Bool)
-> (CalibratedTimestampInfoEXT
    -> CalibratedTimestampInfoEXT -> Bool)
-> Eq CalibratedTimestampInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CalibratedTimestampInfoEXT -> CalibratedTimestampInfoEXT -> Bool
== :: CalibratedTimestampInfoEXT -> CalibratedTimestampInfoEXT -> Bool
$c/= :: CalibratedTimestampInfoEXT -> CalibratedTimestampInfoEXT -> Bool
/= :: CalibratedTimestampInfoEXT -> CalibratedTimestampInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CalibratedTimestampInfoEXT)
#endif
deriving instance Show CalibratedTimestampInfoEXT

instance ToCStruct CalibratedTimestampInfoEXT where
  withCStruct :: forall b.
CalibratedTimestampInfoEXT
-> (Ptr CalibratedTimestampInfoEXT -> IO b) -> IO b
withCStruct CalibratedTimestampInfoEXT
x Ptr CalibratedTimestampInfoEXT -> IO b
f = Int -> (Ptr CalibratedTimestampInfoEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr CalibratedTimestampInfoEXT -> IO b) -> IO b)
-> (Ptr CalibratedTimestampInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr CalibratedTimestampInfoEXT
p -> Ptr CalibratedTimestampInfoEXT
-> CalibratedTimestampInfoEXT -> IO b -> IO b
forall b.
Ptr CalibratedTimestampInfoEXT
-> CalibratedTimestampInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CalibratedTimestampInfoEXT
p CalibratedTimestampInfoEXT
x (Ptr CalibratedTimestampInfoEXT -> IO b
f Ptr CalibratedTimestampInfoEXT
p)
  pokeCStruct :: forall b.
Ptr CalibratedTimestampInfoEXT
-> CalibratedTimestampInfoEXT -> IO b -> IO b
pokeCStruct Ptr CalibratedTimestampInfoEXT
p CalibratedTimestampInfoEXT{TimeDomainEXT
$sel:timeDomain:CalibratedTimestampInfoEXT :: CalibratedTimestampInfoEXT -> TimeDomainEXT
timeDomain :: TimeDomainEXT
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CalibratedTimestampInfoEXT
p Ptr CalibratedTimestampInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_CALIBRATED_TIMESTAMP_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CalibratedTimestampInfoEXT
p Ptr CalibratedTimestampInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr TimeDomainEXT -> TimeDomainEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CalibratedTimestampInfoEXT
p Ptr CalibratedTimestampInfoEXT -> Int -> Ptr TimeDomainEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr TimeDomainEXT)) (TimeDomainEXT
timeDomain)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr CalibratedTimestampInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr CalibratedTimestampInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CalibratedTimestampInfoEXT
p Ptr CalibratedTimestampInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_CALIBRATED_TIMESTAMP_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CalibratedTimestampInfoEXT
p Ptr CalibratedTimestampInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr TimeDomainEXT -> TimeDomainEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CalibratedTimestampInfoEXT
p Ptr CalibratedTimestampInfoEXT -> Int -> Ptr TimeDomainEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr TimeDomainEXT)) (TimeDomainEXT
forall a. Zero a => a
zero)
    IO b
f

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

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

instance Zero CalibratedTimestampInfoEXT where
  zero :: CalibratedTimestampInfoEXT
zero = TimeDomainEXT -> CalibratedTimestampInfoEXT
CalibratedTimestampInfoEXT
           TimeDomainEXT
forall a. Zero a => a
zero


-- | VkTimeDomainEXT - Supported time domains
--
-- = Description
--
-- Note
--
-- An implementation supporting @VK_EXT_calibrated_timestamps@ will use the
-- same time domain for all its 'Vulkan.Core10.Handles.Queue' so that
-- timestamp values reported for 'TIME_DOMAIN_DEVICE_EXT' can be matched to
-- any timestamp captured through
-- 'Vulkan.Core10.CommandBufferBuilding.cmdWriteTimestamp' or
-- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdWriteTimestamp2'
-- .
--
-- > struct timespec tv;
-- > clock_gettime(CLOCK_MONOTONIC, &tv);
-- > return tv.tv_nsec + tv.tv_sec*1000000000ull;
--
-- > struct timespec tv;
-- > clock_gettime(CLOCK_MONOTONIC_RAW, &tv);
-- > return tv.tv_nsec + tv.tv_sec*1000000000ull;
--
-- > LARGE_INTEGER counter;
-- > QueryPerformanceCounter(&counter);
-- > return counter.QuadPart;
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_calibrated_timestamps VK_EXT_calibrated_timestamps>,
-- 'CalibratedTimestampInfoEXT',
-- 'getPhysicalDeviceCalibrateableTimeDomainsEXT'
newtype TimeDomainEXT = TimeDomainEXT Int32
  deriving newtype (TimeDomainEXT -> TimeDomainEXT -> Bool
(TimeDomainEXT -> TimeDomainEXT -> Bool)
-> (TimeDomainEXT -> TimeDomainEXT -> Bool) -> Eq TimeDomainEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TimeDomainEXT -> TimeDomainEXT -> Bool
== :: TimeDomainEXT -> TimeDomainEXT -> Bool
$c/= :: TimeDomainEXT -> TimeDomainEXT -> Bool
/= :: TimeDomainEXT -> TimeDomainEXT -> Bool
Eq, Eq TimeDomainEXT
Eq TimeDomainEXT =>
(TimeDomainEXT -> TimeDomainEXT -> Ordering)
-> (TimeDomainEXT -> TimeDomainEXT -> Bool)
-> (TimeDomainEXT -> TimeDomainEXT -> Bool)
-> (TimeDomainEXT -> TimeDomainEXT -> Bool)
-> (TimeDomainEXT -> TimeDomainEXT -> Bool)
-> (TimeDomainEXT -> TimeDomainEXT -> TimeDomainEXT)
-> (TimeDomainEXT -> TimeDomainEXT -> TimeDomainEXT)
-> Ord TimeDomainEXT
TimeDomainEXT -> TimeDomainEXT -> Bool
TimeDomainEXT -> TimeDomainEXT -> Ordering
TimeDomainEXT -> TimeDomainEXT -> TimeDomainEXT
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
$ccompare :: TimeDomainEXT -> TimeDomainEXT -> Ordering
compare :: TimeDomainEXT -> TimeDomainEXT -> Ordering
$c< :: TimeDomainEXT -> TimeDomainEXT -> Bool
< :: TimeDomainEXT -> TimeDomainEXT -> Bool
$c<= :: TimeDomainEXT -> TimeDomainEXT -> Bool
<= :: TimeDomainEXT -> TimeDomainEXT -> Bool
$c> :: TimeDomainEXT -> TimeDomainEXT -> Bool
> :: TimeDomainEXT -> TimeDomainEXT -> Bool
$c>= :: TimeDomainEXT -> TimeDomainEXT -> Bool
>= :: TimeDomainEXT -> TimeDomainEXT -> Bool
$cmax :: TimeDomainEXT -> TimeDomainEXT -> TimeDomainEXT
max :: TimeDomainEXT -> TimeDomainEXT -> TimeDomainEXT
$cmin :: TimeDomainEXT -> TimeDomainEXT -> TimeDomainEXT
min :: TimeDomainEXT -> TimeDomainEXT -> TimeDomainEXT
Ord, Ptr TimeDomainEXT -> IO TimeDomainEXT
Ptr TimeDomainEXT -> Int -> IO TimeDomainEXT
Ptr TimeDomainEXT -> Int -> TimeDomainEXT -> IO ()
Ptr TimeDomainEXT -> TimeDomainEXT -> IO ()
TimeDomainEXT -> Int
(TimeDomainEXT -> Int)
-> (TimeDomainEXT -> Int)
-> (Ptr TimeDomainEXT -> Int -> IO TimeDomainEXT)
-> (Ptr TimeDomainEXT -> Int -> TimeDomainEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO TimeDomainEXT)
-> (forall b. Ptr b -> Int -> TimeDomainEXT -> IO ())
-> (Ptr TimeDomainEXT -> IO TimeDomainEXT)
-> (Ptr TimeDomainEXT -> TimeDomainEXT -> IO ())
-> Storable TimeDomainEXT
forall b. Ptr b -> Int -> IO TimeDomainEXT
forall b. Ptr b -> Int -> TimeDomainEXT -> 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
$csizeOf :: TimeDomainEXT -> Int
sizeOf :: TimeDomainEXT -> Int
$calignment :: TimeDomainEXT -> Int
alignment :: TimeDomainEXT -> Int
$cpeekElemOff :: Ptr TimeDomainEXT -> Int -> IO TimeDomainEXT
peekElemOff :: Ptr TimeDomainEXT -> Int -> IO TimeDomainEXT
$cpokeElemOff :: Ptr TimeDomainEXT -> Int -> TimeDomainEXT -> IO ()
pokeElemOff :: Ptr TimeDomainEXT -> Int -> TimeDomainEXT -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO TimeDomainEXT
peekByteOff :: forall b. Ptr b -> Int -> IO TimeDomainEXT
$cpokeByteOff :: forall b. Ptr b -> Int -> TimeDomainEXT -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> TimeDomainEXT -> IO ()
$cpeek :: Ptr TimeDomainEXT -> IO TimeDomainEXT
peek :: Ptr TimeDomainEXT -> IO TimeDomainEXT
$cpoke :: Ptr TimeDomainEXT -> TimeDomainEXT -> IO ()
poke :: Ptr TimeDomainEXT -> TimeDomainEXT -> IO ()
Storable, TimeDomainEXT
TimeDomainEXT -> Zero TimeDomainEXT
forall a. a -> Zero a
$czero :: TimeDomainEXT
zero :: TimeDomainEXT
Zero)

-- | 'TIME_DOMAIN_DEVICE_EXT' specifies the device time domain. Timestamp
-- values in this time domain use the same units and are comparable with
-- device timestamp values captured using
-- 'Vulkan.Core10.CommandBufferBuilding.cmdWriteTimestamp' or
-- 'Vulkan.Core13.Promoted_From_VK_KHR_synchronization2.cmdWriteTimestamp2'
-- and are defined to be incrementing according to the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-timestampPeriod timestampPeriod>
-- of the device.
pattern $mTIME_DOMAIN_DEVICE_EXT :: forall {r}. TimeDomainEXT -> ((# #) -> r) -> ((# #) -> r) -> r
$bTIME_DOMAIN_DEVICE_EXT :: TimeDomainEXT
TIME_DOMAIN_DEVICE_EXT = TimeDomainEXT 0

-- | 'TIME_DOMAIN_CLOCK_MONOTONIC_EXT' specifies the CLOCK_MONOTONIC time
-- domain available on POSIX platforms. Timestamp values in this time
-- domain are in units of nanoseconds and are comparable with platform
-- timestamp values captured using the POSIX clock_gettime API as computed
-- by this example:
pattern $mTIME_DOMAIN_CLOCK_MONOTONIC_EXT :: forall {r}. TimeDomainEXT -> ((# #) -> r) -> ((# #) -> r) -> r
$bTIME_DOMAIN_CLOCK_MONOTONIC_EXT :: TimeDomainEXT
TIME_DOMAIN_CLOCK_MONOTONIC_EXT = TimeDomainEXT 1

-- | 'TIME_DOMAIN_CLOCK_MONOTONIC_RAW_EXT' specifies the CLOCK_MONOTONIC_RAW
-- time domain available on POSIX platforms. Timestamp values in this time
-- domain are in units of nanoseconds and are comparable with platform
-- timestamp values captured using the POSIX clock_gettime API as computed
-- by this example:
pattern $mTIME_DOMAIN_CLOCK_MONOTONIC_RAW_EXT :: forall {r}. TimeDomainEXT -> ((# #) -> r) -> ((# #) -> r) -> r
$bTIME_DOMAIN_CLOCK_MONOTONIC_RAW_EXT :: TimeDomainEXT
TIME_DOMAIN_CLOCK_MONOTONIC_RAW_EXT = TimeDomainEXT 2

-- | 'TIME_DOMAIN_QUERY_PERFORMANCE_COUNTER_EXT' specifies the performance
-- counter (QPC) time domain available on Windows. Timestamp values in this
-- time domain are in the same units as those provided by the Windows
-- QueryPerformanceCounter API and are comparable with platform timestamp
-- values captured using that API as computed by this example:
pattern $mTIME_DOMAIN_QUERY_PERFORMANCE_COUNTER_EXT :: forall {r}. TimeDomainEXT -> ((# #) -> r) -> ((# #) -> r) -> r
$bTIME_DOMAIN_QUERY_PERFORMANCE_COUNTER_EXT :: TimeDomainEXT
TIME_DOMAIN_QUERY_PERFORMANCE_COUNTER_EXT = TimeDomainEXT 3

{-# COMPLETE
  TIME_DOMAIN_DEVICE_EXT
  , TIME_DOMAIN_CLOCK_MONOTONIC_EXT
  , TIME_DOMAIN_CLOCK_MONOTONIC_RAW_EXT
  , TIME_DOMAIN_QUERY_PERFORMANCE_COUNTER_EXT ::
    TimeDomainEXT
  #-}

conNameTimeDomainEXT :: String
conNameTimeDomainEXT :: String
conNameTimeDomainEXT = String
"TimeDomainEXT"

enumPrefixTimeDomainEXT :: String
enumPrefixTimeDomainEXT :: String
enumPrefixTimeDomainEXT = String
"TIME_DOMAIN_"

showTableTimeDomainEXT :: [(TimeDomainEXT, String)]
showTableTimeDomainEXT :: [(TimeDomainEXT, String)]
showTableTimeDomainEXT =
  [ (TimeDomainEXT
TIME_DOMAIN_DEVICE_EXT, String
"DEVICE_EXT")
  ,
    ( TimeDomainEXT
TIME_DOMAIN_CLOCK_MONOTONIC_EXT
    , String
"CLOCK_MONOTONIC_EXT"
    )
  ,
    ( TimeDomainEXT
TIME_DOMAIN_CLOCK_MONOTONIC_RAW_EXT
    , String
"CLOCK_MONOTONIC_RAW_EXT"
    )
  ,
    ( TimeDomainEXT
TIME_DOMAIN_QUERY_PERFORMANCE_COUNTER_EXT
    , String
"QUERY_PERFORMANCE_COUNTER_EXT"
    )
  ]

instance Show TimeDomainEXT where
  showsPrec :: Int -> TimeDomainEXT -> ShowS
showsPrec =
    String
-> [(TimeDomainEXT, String)]
-> String
-> (TimeDomainEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> TimeDomainEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixTimeDomainEXT
      [(TimeDomainEXT, String)]
showTableTimeDomainEXT
      String
conNameTimeDomainEXT
      (\(TimeDomainEXT Int32
x) -> Int32
x)
      (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read TimeDomainEXT where
  readPrec :: ReadPrec TimeDomainEXT
readPrec =
    String
-> [(TimeDomainEXT, String)]
-> String
-> (Int32 -> TimeDomainEXT)
-> ReadPrec TimeDomainEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixTimeDomainEXT
      [(TimeDomainEXT, String)]
showTableTimeDomainEXT
      String
conNameTimeDomainEXT
      Int32 -> TimeDomainEXT
TimeDomainEXT

type EXT_CALIBRATED_TIMESTAMPS_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_CALIBRATED_TIMESTAMPS_SPEC_VERSION"
pattern EXT_CALIBRATED_TIMESTAMPS_SPEC_VERSION :: forall a . Integral a => a
pattern $mEXT_CALIBRATED_TIMESTAMPS_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
$bEXT_CALIBRATED_TIMESTAMPS_SPEC_VERSION :: forall a. Integral a => a
EXT_CALIBRATED_TIMESTAMPS_SPEC_VERSION = 2


type EXT_CALIBRATED_TIMESTAMPS_EXTENSION_NAME = "VK_EXT_calibrated_timestamps"

-- No documentation found for TopLevel "VK_EXT_CALIBRATED_TIMESTAMPS_EXTENSION_NAME"
pattern EXT_CALIBRATED_TIMESTAMPS_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $mEXT_CALIBRATED_TIMESTAMPS_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
$bEXT_CALIBRATED_TIMESTAMPS_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
EXT_CALIBRATED_TIMESTAMPS_EXTENSION_NAME = "VK_EXT_calibrated_timestamps"