{-# language CPP #-}
-- | = Name
--
-- VK_INTEL_performance_query - device extension
--
-- == VK_INTEL_performance_query
--
-- [__Name String__]
--     @VK_INTEL_performance_query@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     211
--
-- [__Revision__]
--     2
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
-- [__Special Use__]
--
--     -   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-compatibility-specialuse Developer tools>
--
-- [__Contact__]
--
--     -   Lionel Landwerlin
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_INTEL_performance_query] @llandwerlin%0A*Here describe the issue or question you have about the VK_INTEL_performance_query extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2018-05-16
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Lionel Landwerlin, Intel
--
--     -   Piotr Maciejewski, Intel
--
-- == Description
--
-- This extension allows an application to capture performance data to be
-- interpreted by a external application or library.
--
-- Such a library is available at :
-- <https://github.com/intel/metrics-discovery>
--
-- Performance analysis tools such as
-- <https://software.intel.com/content/www/us/en/develop/tools/graphics-performance-analyzers.html Graphics Performance Analyzers>
-- make use of this extension and the metrics-discovery library to present
-- the data in a human readable way.
--
-- == New Object Types
--
-- -   'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL'
--
-- == New Commands
--
-- -   'acquirePerformanceConfigurationINTEL'
--
-- -   'cmdSetPerformanceMarkerINTEL'
--
-- -   'cmdSetPerformanceOverrideINTEL'
--
-- -   'cmdSetPerformanceStreamMarkerINTEL'
--
-- -   'getPerformanceParameterINTEL'
--
-- -   'initializePerformanceApiINTEL'
--
-- -   'queueSetPerformanceConfigurationINTEL'
--
-- -   'releasePerformanceConfigurationINTEL'
--
-- -   'uninitializePerformanceApiINTEL'
--
-- == New Structures
--
-- -   'InitializePerformanceApiInfoINTEL'
--
-- -   'PerformanceConfigurationAcquireInfoINTEL'
--
-- -   'PerformanceMarkerInfoINTEL'
--
-- -   'PerformanceOverrideInfoINTEL'
--
-- -   'PerformanceStreamMarkerInfoINTEL'
--
-- -   'PerformanceValueINTEL'
--
-- -   Extending 'Vulkan.Core10.Query.QueryPoolCreateInfo':
--
--     -   'QueryPoolCreateInfoINTEL'
--
--     -   'QueryPoolPerformanceQueryCreateInfoINTEL'
--
-- == New Unions
--
-- -   'PerformanceValueDataINTEL'
--
-- == New Enums
--
-- -   'PerformanceConfigurationTypeINTEL'
--
-- -   'PerformanceOverrideTypeINTEL'
--
-- -   'PerformanceParameterTypeINTEL'
--
-- -   'PerformanceValueTypeINTEL'
--
-- -   'QueryPoolSamplingModeINTEL'
--
-- == New Enum Constants
--
-- -   'INTEL_PERFORMANCE_QUERY_EXTENSION_NAME'
--
-- -   'INTEL_PERFORMANCE_QUERY_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.ObjectType.ObjectType':
--
--     -   'Vulkan.Core10.Enums.ObjectType.OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL'
--
-- -   Extending 'Vulkan.Core10.Enums.QueryType.QueryType':
--
--     -   'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_INTEL'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL'
--
--     -   'STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL'
--
-- == Example Code
--
-- > // A previously created device
-- > VkDevice device;
-- >
-- > // A queue derived from the device
-- > VkQueue queue;
-- >
-- > VkInitializePerformanceApiInfoINTEL performanceApiInfoIntel = {
-- >   VK_STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL,
-- >   NULL,
-- >   NULL
-- > };
-- >
-- > vkInitializePerformanceApiINTEL(
-- >   device,
-- >   &performanceApiInfoIntel);
-- >
-- > VkQueryPoolPerformanceQueryCreateInfoINTEL queryPoolIntel = {
-- >   VK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL,
-- >   NULL,
-- >   VK_QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL,
-- > };
-- >
-- > VkQueryPoolCreateInfo queryPoolCreateInfo = {
-- >   VK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO,
-- >   &queryPoolIntel,
-- >   0,
-- >   VK_QUERY_TYPE_PERFORMANCE_QUERY_INTEL,
-- >   1,
-- >   0
-- > };
-- >
-- > VkQueryPool queryPool;
-- >
-- > VkResult result = vkCreateQueryPool(
-- >   device,
-- >   &queryPoolCreateInfo,
-- >   NULL,
-- >   &queryPool);
-- >
-- > assert(VK_SUCCESS == result);
-- >
-- > // A command buffer we want to record counters on
-- > VkCommandBuffer commandBuffer;
-- >
-- > VkCommandBufferBeginInfo commandBufferBeginInfo = {
-- >   VK_STRUCTURE_TYPE_COMMAND_BUFFER_BEGIN_INFO,
-- >   NULL,
-- >   VK_COMMAND_BUFFER_USAGE_ONE_TIME_SUBMIT_BIT,
-- >   NULL
-- > };
-- >
-- > result = vkBeginCommandBuffer(commandBuffer, &commandBufferBeginInfo);
-- >
-- > assert(VK_SUCCESS == result);
-- >
-- > vkCmdResetQueryPool(
-- >   commandBuffer,
-- >   queryPool,
-- >   0,
-- >   1);
-- >
-- > vkCmdBeginQuery(
-- >   commandBuffer,
-- >   queryPool,
-- >   0,
-- >   0);
-- >
-- > // Perform the commands you want to get performance information on
-- > // ...
-- >
-- > // Perform a barrier to ensure all previous commands were complete before
-- > // ending the query
-- > vkCmdPipelineBarrier(commandBuffer,
-- >   VK_PIPELINE_STAGE_BOTTOM_OF_PIPE_BIT,
-- >   VK_PIPELINE_STAGE_BOTTOM_OF_PIPE_BIT,
-- >   0,
-- >   0,
-- >   NULL,
-- >   0,
-- >   NULL,
-- >   0,
-- >   NULL);
-- >
-- > vkCmdEndQuery(
-- >   commandBuffer,
-- >   queryPool,
-- >   0);
-- >
-- > result = vkEndCommandBuffer(commandBuffer);
-- >
-- > assert(VK_SUCCESS == result);
-- >
-- > VkPerformanceConfigurationAcquireInfoINTEL performanceConfigurationAcquireInfo = {
-- >   VK_STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL,
-- >   NULL,
-- >   VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL
-- > };
-- >
-- > VkPerformanceConfigurationINTEL performanceConfigurationIntel;
-- >
-- > result = vkAcquirePerformanceConfigurationINTEL(
-- >   device,
-- >   &performanceConfigurationAcquireInfo,
-- >   &performanceConfigurationIntel);
-- >
-- > vkQueueSetPerformanceConfigurationINTEL(queue, performanceConfigurationIntel);
-- >
-- > assert(VK_SUCCESS == result);
-- >
-- > // Submit the command buffer and wait for its completion
-- > // ...
-- >
-- > result = vkReleasePerformanceConfigurationINTEL(
-- >   device,
-- >   performanceConfigurationIntel);
-- >
-- > assert(VK_SUCCESS == result);
-- >
-- > // Get the report size from metrics-discovery's QueryReportSize
-- >
-- > result = vkGetQueryPoolResults(
-- >   device,
-- >   queryPool,
-- >   0, 1, QueryReportSize,
-- >   data, QueryReportSize, 0);
-- >
-- > assert(VK_SUCCESS == result);
-- >
-- > // The data can then be passed back to metrics-discovery from which
-- > // human readable values can be queried.
--
-- == Version History
--
-- -   Revision 2, 2020-03-06 (Lionel Landwerlin)
--
--     -   Rename VkQueryPoolCreateInfoINTEL in
--         VkQueryPoolPerformanceQueryCreateInfoINTEL
--
-- -   Revision 1, 2018-05-16 (Lionel Landwerlin)
--
--     -   Initial revision
--
-- == See Also
--
-- 'InitializePerformanceApiInfoINTEL',
-- 'PerformanceConfigurationAcquireInfoINTEL',
-- 'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL',
-- 'PerformanceConfigurationTypeINTEL', 'PerformanceMarkerInfoINTEL',
-- 'PerformanceOverrideInfoINTEL', 'PerformanceOverrideTypeINTEL',
-- 'PerformanceParameterTypeINTEL', 'PerformanceStreamMarkerInfoINTEL',
-- 'PerformanceValueDataINTEL', 'PerformanceValueINTEL',
-- 'PerformanceValueTypeINTEL', 'QueryPoolCreateInfoINTEL',
-- 'QueryPoolPerformanceQueryCreateInfoINTEL',
-- 'QueryPoolSamplingModeINTEL', 'acquirePerformanceConfigurationINTEL',
-- 'cmdSetPerformanceMarkerINTEL', 'cmdSetPerformanceOverrideINTEL',
-- 'cmdSetPerformanceStreamMarkerINTEL', 'getPerformanceParameterINTEL',
-- 'initializePerformanceApiINTEL',
-- 'queueSetPerformanceConfigurationINTEL',
-- 'releasePerformanceConfigurationINTEL',
-- 'uninitializePerformanceApiINTEL'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_INTEL_performance_query Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_INTEL_performance_query  ( initializePerformanceApiINTEL
                                                     , uninitializePerformanceApiINTEL
                                                     , cmdSetPerformanceMarkerINTEL
                                                     , cmdSetPerformanceStreamMarkerINTEL
                                                     , cmdSetPerformanceOverrideINTEL
                                                     , acquirePerformanceConfigurationINTEL
                                                     , releasePerformanceConfigurationINTEL
                                                     , queueSetPerformanceConfigurationINTEL
                                                     , getPerformanceParameterINTEL
                                                     , pattern STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL
                                                     , PerformanceValueINTEL(..)
                                                     , InitializePerformanceApiInfoINTEL(..)
                                                     , QueryPoolPerformanceQueryCreateInfoINTEL(..)
                                                     , PerformanceMarkerInfoINTEL(..)
                                                     , PerformanceStreamMarkerInfoINTEL(..)
                                                     , PerformanceOverrideInfoINTEL(..)
                                                     , PerformanceConfigurationAcquireInfoINTEL(..)
                                                     , PerformanceValueDataINTEL(..)
                                                     , peekPerformanceValueDataINTEL
                                                     , PerformanceConfigurationTypeINTEL( PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL
                                                                                        , ..
                                                                                        )
                                                     , QueryPoolSamplingModeINTEL( QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL
                                                                                 , ..
                                                                                 )
                                                     , PerformanceOverrideTypeINTEL( PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL
                                                                                   , PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL
                                                                                   , ..
                                                                                   )
                                                     , PerformanceParameterTypeINTEL( PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL
                                                                                    , PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL
                                                                                    , ..
                                                                                    )
                                                     , PerformanceValueTypeINTEL( PERFORMANCE_VALUE_TYPE_UINT32_INTEL
                                                                                , PERFORMANCE_VALUE_TYPE_UINT64_INTEL
                                                                                , PERFORMANCE_VALUE_TYPE_FLOAT_INTEL
                                                                                , PERFORMANCE_VALUE_TYPE_BOOL_INTEL
                                                                                , PERFORMANCE_VALUE_TYPE_STRING_INTEL
                                                                                , ..
                                                                                )
                                                     , QueryPoolCreateInfoINTEL
                                                     , INTEL_PERFORMANCE_QUERY_SPEC_VERSION
                                                     , pattern INTEL_PERFORMANCE_QUERY_SPEC_VERSION
                                                     , INTEL_PERFORMANCE_QUERY_EXTENSION_NAME
                                                     , pattern INTEL_PERFORMANCE_QUERY_EXTENSION_NAME
                                                     , PerformanceConfigurationINTEL(..)
                                                     ) 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 (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showsPrec)
import Data.ByteString (packCString)
import Data.ByteString (useAsCString)
import Data.Coerce (coerce)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.Trans.Cont (runContT)
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.C.Types (CChar)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(..))
import Foreign.C.Types (CFloat(CFloat))
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.ByteString (ByteString)
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 (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkAcquirePerformanceConfigurationINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetPerformanceMarkerINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetPerformanceOverrideINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetPerformanceStreamMarkerINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkGetPerformanceParameterINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkInitializePerformanceApiINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkQueueSetPerformanceConfigurationINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkReleasePerformanceConfigurationINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkUninitializePerformanceApiINTEL))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Extensions.Handles (PerformanceConfigurationINTEL)
import Vulkan.Extensions.Handles (PerformanceConfigurationINTEL(..))
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.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.Handles (PerformanceConfigurationINTEL(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkInitializePerformanceApiINTEL
  :: FunPtr (Ptr Device_T -> Ptr InitializePerformanceApiInfoINTEL -> IO Result) -> Ptr Device_T -> Ptr InitializePerformanceApiInfoINTEL -> IO Result

-- | vkInitializePerformanceApiINTEL - Initialize a device for performance
-- queries
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Handles.Device', 'InitializePerformanceApiInfoINTEL'
initializePerformanceApiINTEL :: forall io
                               . (MonadIO io)
                              => -- | @device@ is the logical device used for the queries.
                                 --
                                 -- #VUID-vkInitializePerformanceApiINTEL-device-parameter# @device@ /must/
                                 -- be a valid 'Vulkan.Core10.Handles.Device' handle
                                 Device
                              -> -- | @pInitializeInfo@ is a pointer to a 'InitializePerformanceApiInfoINTEL'
                                 -- structure specifying initialization parameters.
                                 --
                                 -- #VUID-vkInitializePerformanceApiINTEL-pInitializeInfo-parameter#
                                 -- @pInitializeInfo@ /must/ be a valid pointer to a valid
                                 -- 'InitializePerformanceApiInfoINTEL' structure
                                 ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
                              -> io ()
initializePerformanceApiINTEL :: forall (io :: * -> *).
MonadIO io =>
Device -> InitializePerformanceApiInfoINTEL -> io ()
initializePerformanceApiINTEL Device
device InitializePerformanceApiInfoINTEL
initializeInfo = 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 vkInitializePerformanceApiINTELPtr :: FunPtr
  (Ptr Device_T
   -> ("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
   -> IO Result)
vkInitializePerformanceApiINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
      -> IO Result)
pVkInitializePerformanceApiINTEL (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
   -> ("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
   -> IO Result)
vkInitializePerformanceApiINTELPtr 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 vkInitializePerformanceApiINTEL is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkInitializePerformanceApiINTEL' :: Ptr Device_T
-> ("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
-> IO Result
vkInitializePerformanceApiINTEL' = FunPtr
  (Ptr Device_T
   -> ("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
   -> IO Result)
-> Ptr Device_T
-> ("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
-> IO Result
mkVkInitializePerformanceApiINTEL FunPtr
  (Ptr Device_T
   -> ("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
   -> IO Result)
vkInitializePerformanceApiINTELPtr
  "pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
pInitializeInfo <- 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 (InitializePerformanceApiInfoINTEL
initializeInfo)
  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
"vkInitializePerformanceApiINTEL" (Ptr Device_T
-> ("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
-> IO Result
vkInitializePerformanceApiINTEL'
                                                                    (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                    "pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
pInitializeInfo)
  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" mkVkUninitializePerformanceApiINTEL
  :: FunPtr (Ptr Device_T -> IO ()) -> Ptr Device_T -> IO ()

-- | vkUninitializePerformanceApiINTEL - Uninitialize a device for
-- performance queries
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Handles.Device'
uninitializePerformanceApiINTEL :: forall io
                                 . (MonadIO io)
                                => -- | @device@ is the logical device used for the queries.
                                   --
                                   -- #VUID-vkUninitializePerformanceApiINTEL-device-parameter# @device@
                                   -- /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                   Device
                                -> io ()
uninitializePerformanceApiINTEL :: forall (io :: * -> *). MonadIO io => Device -> io ()
uninitializePerformanceApiINTEL Device
device = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkUninitializePerformanceApiINTELPtr :: FunPtr (Ptr Device_T -> IO ())
vkUninitializePerformanceApiINTELPtr = DeviceCmds -> FunPtr (Ptr Device_T -> IO ())
pVkUninitializePerformanceApiINTEL (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> IO ())
vkUninitializePerformanceApiINTELPtr 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 vkUninitializePerformanceApiINTEL is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkUninitializePerformanceApiINTEL' :: Ptr Device_T -> IO ()
vkUninitializePerformanceApiINTEL' = FunPtr (Ptr Device_T -> IO ()) -> Ptr Device_T -> IO ()
mkVkUninitializePerformanceApiINTEL FunPtr (Ptr Device_T -> IO ())
vkUninitializePerformanceApiINTELPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkUninitializePerformanceApiINTEL" (Ptr Device_T -> IO ()
vkUninitializePerformanceApiINTEL'
                                                          (Device -> Ptr Device_T
deviceHandle (Device
device)))
  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" mkVkCmdSetPerformanceMarkerINTEL
  :: FunPtr (Ptr CommandBuffer_T -> Ptr PerformanceMarkerInfoINTEL -> IO Result) -> Ptr CommandBuffer_T -> Ptr PerformanceMarkerInfoINTEL -> IO Result

-- | vkCmdSetPerformanceMarkerINTEL - Markers
--
-- = Parameters
--
-- The last marker set onto a command buffer before the end of a query will
-- be part of the query result.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetPerformanceMarkerINTEL-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetPerformanceMarkerINTEL-pMarkerInfo-parameter#
--     @pMarkerInfo@ /must/ be a valid pointer to a valid
--     'PerformanceMarkerInfoINTEL' structure
--
-- -   #VUID-vkCmdSetPerformanceMarkerINTEL-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdSetPerformanceMarkerINTEL-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, compute, or transfer
--     operations
--
-- -   #VUID-vkCmdSetPerformanceMarkerINTEL-videocoding# This command
--     /must/ only be called outside of a video coding scope
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Outside                                                                                                                     | Graphics                                                                                                              | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             | Compute                                                                                                               | State                                                                                                                                  |
-- |                                                                                                                            |                                                                                                                        |                                                                                                                             | Transfer                                                                                                              |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'PerformanceMarkerInfoINTEL'
cmdSetPerformanceMarkerINTEL :: forall io
                              . (MonadIO io)
                             => -- No documentation found for Nested "vkCmdSetPerformanceMarkerINTEL" "commandBuffer"
                                CommandBuffer
                             -> -- No documentation found for Nested "vkCmdSetPerformanceMarkerINTEL" "pMarkerInfo"
                                PerformanceMarkerInfoINTEL
                             -> io ()
cmdSetPerformanceMarkerINTEL :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> PerformanceMarkerInfoINTEL -> io ()
cmdSetPerformanceMarkerINTEL CommandBuffer
commandBuffer PerformanceMarkerInfoINTEL
markerInfo = 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 vkCmdSetPerformanceMarkerINTELPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
vkCmdSetPerformanceMarkerINTELPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
pVkCmdSetPerformanceMarkerINTEL (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> 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 CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
vkCmdSetPerformanceMarkerINTELPtr 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 vkCmdSetPerformanceMarkerINTEL is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetPerformanceMarkerINTEL' :: Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result
vkCmdSetPerformanceMarkerINTEL' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
-> Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> IO Result
mkVkCmdSetPerformanceMarkerINTEL FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
vkCmdSetPerformanceMarkerINTELPtr
  "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
pMarkerInfo <- 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 (PerformanceMarkerInfoINTEL
markerInfo)
  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
"vkCmdSetPerformanceMarkerINTEL" (Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result
vkCmdSetPerformanceMarkerINTEL'
                                                                   (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                                   "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
pMarkerInfo)
  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" mkVkCmdSetPerformanceStreamMarkerINTEL
  :: FunPtr (Ptr CommandBuffer_T -> Ptr PerformanceStreamMarkerInfoINTEL -> IO Result) -> Ptr CommandBuffer_T -> Ptr PerformanceStreamMarkerInfoINTEL -> IO Result

-- | vkCmdSetPerformanceStreamMarkerINTEL - Markers
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetPerformanceStreamMarkerINTEL-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetPerformanceStreamMarkerINTEL-pMarkerInfo-parameter#
--     @pMarkerInfo@ /must/ be a valid pointer to a valid
--     'PerformanceStreamMarkerInfoINTEL' structure
--
-- -   #VUID-vkCmdSetPerformanceStreamMarkerINTEL-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdSetPerformanceStreamMarkerINTEL-commandBuffer-cmdpool#
--     The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, compute, or transfer
--     operations
--
-- -   #VUID-vkCmdSetPerformanceStreamMarkerINTEL-videocoding# This command
--     /must/ only be called outside of a video coding scope
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Outside                                                                                                                     | Graphics                                                                                                              | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             | Compute                                                                                                               | State                                                                                                                                  |
-- |                                                                                                                            |                                                                                                                        |                                                                                                                             | Transfer                                                                                                              |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'PerformanceStreamMarkerInfoINTEL'
cmdSetPerformanceStreamMarkerINTEL :: forall io
                                    . (MonadIO io)
                                   => -- No documentation found for Nested "vkCmdSetPerformanceStreamMarkerINTEL" "commandBuffer"
                                      CommandBuffer
                                   -> -- No documentation found for Nested "vkCmdSetPerformanceStreamMarkerINTEL" "pMarkerInfo"
                                      PerformanceStreamMarkerInfoINTEL
                                   -> io ()
cmdSetPerformanceStreamMarkerINTEL :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> PerformanceStreamMarkerInfoINTEL -> io ()
cmdSetPerformanceStreamMarkerINTEL CommandBuffer
commandBuffer
                                     PerformanceStreamMarkerInfoINTEL
markerInfo = 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 vkCmdSetPerformanceStreamMarkerINTELPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceStreamMarkerINTELPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
      -> IO Result)
pVkCmdSetPerformanceStreamMarkerINTEL (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> 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 CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceStreamMarkerINTELPtr 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 vkCmdSetPerformanceStreamMarkerINTEL is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetPerformanceStreamMarkerINTEL' :: Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> IO Result
vkCmdSetPerformanceStreamMarkerINTEL' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> IO Result)
-> Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> IO Result
mkVkCmdSetPerformanceStreamMarkerINTEL FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceStreamMarkerINTELPtr
  "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
pMarkerInfo <- 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 (PerformanceStreamMarkerInfoINTEL
markerInfo)
  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
"vkCmdSetPerformanceStreamMarkerINTEL" (Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> IO Result
vkCmdSetPerformanceStreamMarkerINTEL'
                                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                                         "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
pMarkerInfo)
  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" mkVkCmdSetPerformanceOverrideINTEL
  :: FunPtr (Ptr CommandBuffer_T -> Ptr PerformanceOverrideInfoINTEL -> IO Result) -> Ptr CommandBuffer_T -> Ptr PerformanceOverrideInfoINTEL -> IO Result

-- | vkCmdSetPerformanceOverrideINTEL - Performance override settings
--
-- == Valid Usage
--
-- -   #VUID-vkCmdSetPerformanceOverrideINTEL-pOverrideInfo-02736#
--     @pOverrideInfo@ /must/ not be used with a
--     'PerformanceOverrideTypeINTEL' that is not reported available by
--     'getPerformanceParameterINTEL'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdSetPerformanceOverrideINTEL-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdSetPerformanceOverrideINTEL-pOverrideInfo-parameter#
--     @pOverrideInfo@ /must/ be a valid pointer to a valid
--     'PerformanceOverrideInfoINTEL' structure
--
-- -   #VUID-vkCmdSetPerformanceOverrideINTEL-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdSetPerformanceOverrideINTEL-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, compute, or transfer
--     operations
--
-- -   #VUID-vkCmdSetPerformanceOverrideINTEL-videocoding# This command
--     /must/ only be called outside of a video coding scope
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Outside                                                                                                                     | Graphics                                                                                                              | State                                                                                                                                  |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             | Compute                                                                                                               |                                                                                                                                        |
-- |                                                                                                                            |                                                                                                                        |                                                                                                                             | Transfer                                                                                                              |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'PerformanceOverrideInfoINTEL'
cmdSetPerformanceOverrideINTEL :: forall io
                                . (MonadIO io)
                               => -- | @commandBuffer@ is the command buffer where the override takes place.
                                  CommandBuffer
                               -> -- | @pOverrideInfo@ is a pointer to a 'PerformanceOverrideInfoINTEL'
                                  -- structure selecting the parameter to override.
                                  PerformanceOverrideInfoINTEL
                               -> io ()
cmdSetPerformanceOverrideINTEL :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> PerformanceOverrideInfoINTEL -> io ()
cmdSetPerformanceOverrideINTEL CommandBuffer
commandBuffer
                                 PerformanceOverrideInfoINTEL
overrideInfo = 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 vkCmdSetPerformanceOverrideINTELPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceOverrideINTELPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
      -> IO Result)
pVkCmdSetPerformanceOverrideINTEL (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> 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 CommandBuffer_T
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceOverrideINTELPtr 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 vkCmdSetPerformanceOverrideINTEL is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdSetPerformanceOverrideINTEL' :: Ptr CommandBuffer_T
-> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO Result
vkCmdSetPerformanceOverrideINTEL' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> IO Result)
-> Ptr CommandBuffer_T
-> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO Result
mkVkCmdSetPerformanceOverrideINTEL FunPtr
  (Ptr CommandBuffer_T
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceOverrideINTELPtr
  "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
pOverrideInfo <- 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 (PerformanceOverrideInfoINTEL
overrideInfo)
  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
"vkCmdSetPerformanceOverrideINTEL" (Ptr CommandBuffer_T
-> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO Result
vkCmdSetPerformanceOverrideINTEL'
                                                                     (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                                     "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
pOverrideInfo)
  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" mkVkAcquirePerformanceConfigurationINTEL
  :: FunPtr (Ptr Device_T -> Ptr PerformanceConfigurationAcquireInfoINTEL -> Ptr PerformanceConfigurationINTEL -> IO Result) -> Ptr Device_T -> Ptr PerformanceConfigurationAcquireInfoINTEL -> Ptr PerformanceConfigurationINTEL -> IO Result

-- | vkAcquirePerformanceConfigurationINTEL - Acquire the performance query
-- capability
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Handles.Device',
-- 'PerformanceConfigurationAcquireInfoINTEL',
-- 'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL'
acquirePerformanceConfigurationINTEL :: forall io
                                      . (MonadIO io)
                                     => -- | @device@ is the logical device that the performance query commands will
                                        -- be submitted to.
                                        --
                                        -- #VUID-vkAcquirePerformanceConfigurationINTEL-device-parameter# @device@
                                        -- /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                        Device
                                     -> -- | @pAcquireInfo@ is a pointer to a
                                        -- 'PerformanceConfigurationAcquireInfoINTEL' structure, specifying the
                                        -- performance configuration to acquire.
                                        --
                                        -- #VUID-vkAcquirePerformanceConfigurationINTEL-pAcquireInfo-parameter#
                                        -- @pAcquireInfo@ /must/ be a valid pointer to a valid
                                        -- 'PerformanceConfigurationAcquireInfoINTEL' structure
                                        PerformanceConfigurationAcquireInfoINTEL
                                     -> io (PerformanceConfigurationINTEL)
acquirePerformanceConfigurationINTEL :: forall (io :: * -> *).
MonadIO io =>
Device
-> PerformanceConfigurationAcquireInfoINTEL
-> io PerformanceConfigurationINTEL
acquirePerformanceConfigurationINTEL Device
device
                                       PerformanceConfigurationAcquireInfoINTEL
acquireInfo = 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 vkAcquirePerformanceConfigurationINTELPtr :: FunPtr
  (Ptr Device_T
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO Result)
vkAcquirePerformanceConfigurationINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pAcquireInfo"
          ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
      -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
      -> IO Result)
pVkAcquirePerformanceConfigurationINTEL (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
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO Result)
vkAcquirePerformanceConfigurationINTELPtr 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 vkAcquirePerformanceConfigurationINTEL is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkAcquirePerformanceConfigurationINTEL' :: Ptr Device_T
-> ("pAcquireInfo"
    ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
-> IO Result
vkAcquirePerformanceConfigurationINTEL' = FunPtr
  (Ptr Device_T
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO Result)
-> Ptr Device_T
-> ("pAcquireInfo"
    ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
-> IO Result
mkVkAcquirePerformanceConfigurationINTEL FunPtr
  (Ptr Device_T
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO Result)
vkAcquirePerformanceConfigurationINTELPtr
  "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
pAcquireInfo <- 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 (PerformanceConfigurationAcquireInfoINTEL
acquireInfo)
  "pConfiguration" ::: Ptr PerformanceConfigurationINTEL
pPConfiguration <- 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 @PerformanceConfigurationINTEL Int
8) forall a. Ptr a -> IO ()
free
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkAcquirePerformanceConfigurationINTEL" (Ptr Device_T
-> ("pAcquireInfo"
    ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
-> IO Result
vkAcquirePerformanceConfigurationINTEL'
                                                                           (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                           "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
pAcquireInfo
                                                                           ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL
pPConfiguration))
  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))
  PerformanceConfigurationINTEL
pConfiguration <- 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 @PerformanceConfigurationINTEL "pConfiguration" ::: Ptr PerformanceConfigurationINTEL
pPConfiguration
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (PerformanceConfigurationINTEL
pConfiguration)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkReleasePerformanceConfigurationINTEL
  :: FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result) -> Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result

-- | vkReleasePerformanceConfigurationINTEL - Release a configuration to
-- capture performance data
--
-- == Valid Usage
--
-- -   #VUID-vkReleasePerformanceConfigurationINTEL-configuration-02737#
--     @configuration@ /must/ not be released before all command buffers
--     submitted while the configuration was set are in
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#commandbuffers-lifecycle pending state>
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkReleasePerformanceConfigurationINTEL-device-parameter#
--     @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkReleasePerformanceConfigurationINTEL-configuration-parameter#
--     If @configuration@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @configuration@ /must/ be a valid
--     'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL' handle
--
-- -   #VUID-vkReleasePerformanceConfigurationINTEL-configuration-parent#
--     If @configuration@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Host Synchronization
--
-- -   Host access to @configuration@ /must/ be externally synchronized
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL'
releasePerformanceConfigurationINTEL :: forall io
                                      . (MonadIO io)
                                     => -- | @device@ is the device associated to the configuration object to
                                        -- release.
                                        Device
                                     -> -- | @configuration@ is the configuration object to release.
                                        PerformanceConfigurationINTEL
                                     -> io ()
releasePerformanceConfigurationINTEL :: forall (io :: * -> *).
MonadIO io =>
Device -> PerformanceConfigurationINTEL -> io ()
releasePerformanceConfigurationINTEL Device
device PerformanceConfigurationINTEL
configuration = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkReleasePerformanceConfigurationINTELPtr :: FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
vkReleasePerformanceConfigurationINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
pVkReleasePerformanceConfigurationINTEL (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
vkReleasePerformanceConfigurationINTELPtr 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 vkReleasePerformanceConfigurationINTEL is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkReleasePerformanceConfigurationINTEL' :: Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result
vkReleasePerformanceConfigurationINTEL' = FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
-> Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result
mkVkReleasePerformanceConfigurationINTEL FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
vkReleasePerformanceConfigurationINTELPtr
  Result
r <- forall a. String -> IO a -> IO a
traceAroundEvent String
"vkReleasePerformanceConfigurationINTEL" (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result
vkReleasePerformanceConfigurationINTEL'
                                                                    (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                    (PerformanceConfigurationINTEL
configuration))
  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" mkVkQueueSetPerformanceConfigurationINTEL
  :: FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result) -> Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result

-- | vkQueueSetPerformanceConfigurationINTEL - Set a performance query
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkQueueSetPerformanceConfigurationINTEL-queue-parameter#
--     @queue@ /must/ be a valid 'Vulkan.Core10.Handles.Queue' handle
--
-- -   #VUID-vkQueueSetPerformanceConfigurationINTEL-configuration-parameter#
--     @configuration@ /must/ be a valid
--     'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL' handle
--
-- -   #VUID-vkQueueSetPerformanceConfigurationINTEL-commonparent# Both of
--     @configuration@, and @queue@ /must/ have been created, allocated, or
--     retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL',
-- 'Vulkan.Core10.Handles.Queue'
queueSetPerformanceConfigurationINTEL :: forall io
                                       . (MonadIO io)
                                      => -- | @queue@ is the queue on which the configuration will be used.
                                         Queue
                                      -> -- | @configuration@ is the configuration to use.
                                         PerformanceConfigurationINTEL
                                      -> io ()
queueSetPerformanceConfigurationINTEL :: forall (io :: * -> *).
MonadIO io =>
Queue -> PerformanceConfigurationINTEL -> io ()
queueSetPerformanceConfigurationINTEL Queue
queue PerformanceConfigurationINTEL
configuration = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkQueueSetPerformanceConfigurationINTELPtr :: FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
vkQueueSetPerformanceConfigurationINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
pVkQueueSetPerformanceConfigurationINTEL (case Queue
queue of Queue{DeviceCmds
$sel:deviceCmds:Queue :: Queue -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
vkQueueSetPerformanceConfigurationINTELPtr 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 vkQueueSetPerformanceConfigurationINTEL is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkQueueSetPerformanceConfigurationINTEL' :: Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result
vkQueueSetPerformanceConfigurationINTEL' = FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
-> Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result
mkVkQueueSetPerformanceConfigurationINTEL FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
vkQueueSetPerformanceConfigurationINTELPtr
  Result
r <- forall a. String -> IO a -> IO a
traceAroundEvent String
"vkQueueSetPerformanceConfigurationINTEL" (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result
vkQueueSetPerformanceConfigurationINTEL'
                                                                     (Queue -> Ptr Queue_T
queueHandle (Queue
queue))
                                                                     (PerformanceConfigurationINTEL
configuration))
  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" mkVkGetPerformanceParameterINTEL
  :: FunPtr (Ptr Device_T -> PerformanceParameterTypeINTEL -> Ptr PerformanceValueINTEL -> IO Result) -> Ptr Device_T -> PerformanceParameterTypeINTEL -> Ptr PerformanceValueINTEL -> IO Result

-- | vkGetPerformanceParameterINTEL - Query performance capabilities of the
-- device
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Handles.Device', 'PerformanceParameterTypeINTEL',
-- 'PerformanceValueINTEL'
getPerformanceParameterINTEL :: forall io
                              . (MonadIO io)
                             => -- | @device@ is the logical device to query.
                                --
                                -- #VUID-vkGetPerformanceParameterINTEL-device-parameter# @device@ /must/
                                -- be a valid 'Vulkan.Core10.Handles.Device' handle
                                Device
                             -> -- | @parameter@ is the parameter to query.
                                --
                                -- #VUID-vkGetPerformanceParameterINTEL-parameter-parameter# @parameter@
                                -- /must/ be a valid 'PerformanceParameterTypeINTEL' value
                                PerformanceParameterTypeINTEL
                             -> io (PerformanceValueINTEL)
getPerformanceParameterINTEL :: forall (io :: * -> *).
MonadIO io =>
Device -> PerformanceParameterTypeINTEL -> io PerformanceValueINTEL
getPerformanceParameterINTEL Device
device PerformanceParameterTypeINTEL
parameter = 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 vkGetPerformanceParameterINTELPtr :: FunPtr
  (Ptr Device_T
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> IO Result)
vkGetPerformanceParameterINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> PerformanceParameterTypeINTEL
      -> ("pValue" ::: Ptr PerformanceValueINTEL)
      -> IO Result)
pVkGetPerformanceParameterINTEL (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
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> IO Result)
vkGetPerformanceParameterINTELPtr 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 vkGetPerformanceParameterINTEL is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkGetPerformanceParameterINTEL' :: Ptr Device_T
-> PerformanceParameterTypeINTEL
-> ("pValue" ::: Ptr PerformanceValueINTEL)
-> IO Result
vkGetPerformanceParameterINTEL' = FunPtr
  (Ptr Device_T
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> IO Result)
-> Ptr Device_T
-> PerformanceParameterTypeINTEL
-> ("pValue" ::: Ptr PerformanceValueINTEL)
-> IO Result
mkVkGetPerformanceParameterINTEL FunPtr
  (Ptr Device_T
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> IO Result)
vkGetPerformanceParameterINTELPtr
  "pValue" ::: Ptr PerformanceValueINTEL
pPValue <- 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 @PerformanceValueINTEL)
  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
"vkGetPerformanceParameterINTEL" (Ptr Device_T
-> PerformanceParameterTypeINTEL
-> ("pValue" ::: Ptr PerformanceValueINTEL)
-> IO Result
vkGetPerformanceParameterINTEL'
                                                                   (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                   (PerformanceParameterTypeINTEL
parameter)
                                                                   ("pValue" ::: Ptr PerformanceValueINTEL
pPValue))
  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))
  PerformanceValueINTEL
pValue <- 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 @PerformanceValueINTEL "pValue" ::: Ptr PerformanceValueINTEL
pPValue
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (PerformanceValueINTEL
pValue)


-- No documentation found for TopLevel "VK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL"
pattern $bSTRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL :: StructureType
$mSTRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL :: forall {r}. StructureType -> ((# #) -> r) -> ((# #) -> r) -> r
STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL = STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL


-- | VkPerformanceValueINTEL - Container for value and types of parameters
-- that can be queried
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkPerformanceValueINTEL-type-parameter# @type@ /must/ be a
--     valid 'PerformanceValueTypeINTEL' value
--
-- -   #VUID-VkPerformanceValueINTEL-valueString-parameter# If @type@ is
--     'PERFORMANCE_VALUE_TYPE_STRING_INTEL', the @valueString@ member of
--     @data@ /must/ be a null-terminated UTF-8 string
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'PerformanceValueDataINTEL', 'PerformanceValueTypeINTEL',
-- 'getPerformanceParameterINTEL'
data PerformanceValueINTEL = PerformanceValueINTEL
  { -- | @type@ is a 'PerformanceValueTypeINTEL' value specifying the type of the
    -- returned data.
    PerformanceValueINTEL -> PerformanceValueTypeINTEL
type' :: PerformanceValueTypeINTEL
  , -- | @data@ is a 'PerformanceValueDataINTEL' union specifying the value of
    -- the returned data.
    PerformanceValueINTEL -> PerformanceValueDataINTEL
data' :: PerformanceValueDataINTEL
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceValueINTEL)
#endif
deriving instance Show PerformanceValueINTEL

instance ToCStruct PerformanceValueINTEL where
  withCStruct :: forall b.
PerformanceValueINTEL
-> (("pValue" ::: Ptr PerformanceValueINTEL) -> IO b) -> IO b
withCStruct PerformanceValueINTEL
x ("pValue" ::: Ptr PerformanceValueINTEL) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
16 forall a b. (a -> b) -> a -> b
$ \"pValue" ::: Ptr PerformanceValueINTEL
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pValue" ::: Ptr PerformanceValueINTEL
p PerformanceValueINTEL
x (("pValue" ::: Ptr PerformanceValueINTEL) -> IO b
f "pValue" ::: Ptr PerformanceValueINTEL
p)
  pokeCStruct :: forall b.
("pValue" ::: Ptr PerformanceValueINTEL)
-> PerformanceValueINTEL -> IO b -> IO b
pokeCStruct "pValue" ::: Ptr PerformanceValueINTEL
p PerformanceValueINTEL{PerformanceValueTypeINTEL
PerformanceValueDataINTEL
data' :: PerformanceValueDataINTEL
type' :: PerformanceValueTypeINTEL
$sel:data':PerformanceValueINTEL :: PerformanceValueINTEL -> PerformanceValueDataINTEL
$sel:type':PerformanceValueINTEL :: PerformanceValueINTEL -> PerformanceValueTypeINTEL
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    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 -> a -> IO ()
poke (("pValue" ::: Ptr PerformanceValueINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr PerformanceValueTypeINTEL)) (PerformanceValueTypeINTEL
type')
    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 => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pValue" ::: Ptr PerformanceValueINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr PerformanceValueDataINTEL)) (PerformanceValueDataINTEL
data') forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
16
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. ("pValue" ::: Ptr PerformanceValueINTEL) -> IO b -> IO b
pokeZeroCStruct "pValue" ::: Ptr PerformanceValueINTEL
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    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 -> a -> IO ()
poke (("pValue" ::: Ptr PerformanceValueINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr PerformanceValueTypeINTEL)) (forall a. Zero a => a
zero)
    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 => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pValue" ::: Ptr PerformanceValueINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr PerformanceValueDataINTEL)) (forall a. Zero a => a
zero) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a b. (a -> b) -> a -> b
$ ())
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct PerformanceValueINTEL where
  peekCStruct :: ("pValue" ::: Ptr PerformanceValueINTEL)
-> IO PerformanceValueINTEL
peekCStruct "pValue" ::: Ptr PerformanceValueINTEL
p = do
    PerformanceValueTypeINTEL
type' <- forall a. Storable a => Ptr a -> IO a
peek @PerformanceValueTypeINTEL (("pValue" ::: Ptr PerformanceValueINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr PerformanceValueTypeINTEL))
    PerformanceValueDataINTEL
data' <- PerformanceValueTypeINTEL
-> Ptr PerformanceValueDataINTEL -> IO PerformanceValueDataINTEL
peekPerformanceValueDataINTEL PerformanceValueTypeINTEL
type' (("pValue" ::: Ptr PerformanceValueINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr PerformanceValueDataINTEL))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PerformanceValueTypeINTEL
-> PerformanceValueDataINTEL -> PerformanceValueINTEL
PerformanceValueINTEL
             PerformanceValueTypeINTEL
type' PerformanceValueDataINTEL
data'

instance Zero PerformanceValueINTEL where
  zero :: PerformanceValueINTEL
zero = PerformanceValueTypeINTEL
-> PerformanceValueDataINTEL -> PerformanceValueINTEL
PerformanceValueINTEL
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkInitializePerformanceApiInfoINTEL - Structure specifying parameters of
-- initialize of the device
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'initializePerformanceApiINTEL'
data InitializePerformanceApiInfoINTEL = InitializePerformanceApiInfoINTEL
  { -- | @pUserData@ is a pointer for application data.
    InitializePerformanceApiInfoINTEL -> Ptr ()
userData :: Ptr () }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (InitializePerformanceApiInfoINTEL)
#endif
deriving instance Show InitializePerformanceApiInfoINTEL

instance ToCStruct InitializePerformanceApiInfoINTEL where
  withCStruct :: forall b.
InitializePerformanceApiInfoINTEL
-> (("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
    -> IO b)
-> IO b
withCStruct InitializePerformanceApiInfoINTEL
x ("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
-> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
p InitializePerformanceApiInfoINTEL
x (("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
-> IO b
f "pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
p)
  pokeCStruct :: forall b.
("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
-> InitializePerformanceApiInfoINTEL -> IO b -> IO b
pokeCStruct "pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
p InitializePerformanceApiInfoINTEL{Ptr ()
userData :: Ptr ()
$sel:userData:InitializePerformanceApiInfoINTEL :: InitializePerformanceApiInfoINTEL -> Ptr ()
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
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 (("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr ()))) (Ptr ()
userData)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL)
-> IO b -> IO b
pokeZeroCStruct "pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo" ::: Ptr InitializePerformanceApiInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    IO b
f

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

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

instance Zero InitializePerformanceApiInfoINTEL where
  zero :: InitializePerformanceApiInfoINTEL
zero = Ptr () -> InitializePerformanceApiInfoINTEL
InitializePerformanceApiInfoINTEL
           forall a. Zero a => a
zero


-- | VkQueryPoolPerformanceQueryCreateInfoINTEL - Structure specifying
-- parameters to create a pool of performance queries
--
-- = Members
--
-- To create a pool for Intel performance queries, set
-- 'Vulkan.Core10.Query.QueryPoolCreateInfo'::@queryType@ to
-- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_INTEL' and
-- add a 'QueryPoolPerformanceQueryCreateInfoINTEL' structure to the
-- @pNext@ chain of the 'Vulkan.Core10.Query.QueryPoolCreateInfo'
-- structure.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'QueryPoolSamplingModeINTEL',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data QueryPoolPerformanceQueryCreateInfoINTEL = QueryPoolPerformanceQueryCreateInfoINTEL
  { -- | @performanceCountersSampling@ describe how performance queries should be
    -- captured.
    --
    -- #VUID-VkQueryPoolPerformanceQueryCreateInfoINTEL-performanceCountersSampling-parameter#
    -- @performanceCountersSampling@ /must/ be a valid
    -- 'QueryPoolSamplingModeINTEL' value
    QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolSamplingModeINTEL
performanceCountersSampling :: QueryPoolSamplingModeINTEL }
  deriving (Typeable, QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
$c/= :: QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
== :: QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
$c== :: QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (QueryPoolPerformanceQueryCreateInfoINTEL)
#endif
deriving instance Show QueryPoolPerformanceQueryCreateInfoINTEL

instance ToCStruct QueryPoolPerformanceQueryCreateInfoINTEL where
  withCStruct :: forall b.
QueryPoolPerformanceQueryCreateInfoINTEL
-> (Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b) -> IO b
withCStruct QueryPoolPerformanceQueryCreateInfoINTEL
x Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p QueryPoolPerformanceQueryCreateInfoINTEL
x (Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b
f Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p)
  pokeCStruct :: forall b.
Ptr QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> IO b -> IO b
pokeCStruct Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p QueryPoolPerformanceQueryCreateInfoINTEL{QueryPoolSamplingModeINTEL
performanceCountersSampling :: QueryPoolSamplingModeINTEL
$sel:performanceCountersSampling:QueryPoolPerformanceQueryCreateInfoINTEL :: QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolSamplingModeINTEL
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
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 QueryPoolPerformanceQueryCreateInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr QueryPoolSamplingModeINTEL)) (QueryPoolSamplingModeINTEL
performanceCountersSampling)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b -> IO b
pokeZeroCStruct Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
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 QueryPoolPerformanceQueryCreateInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr QueryPoolSamplingModeINTEL)) (forall a. Zero a => a
zero)
    IO b
f

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

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

instance Zero QueryPoolPerformanceQueryCreateInfoINTEL where
  zero :: QueryPoolPerformanceQueryCreateInfoINTEL
zero = QueryPoolSamplingModeINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL
QueryPoolPerformanceQueryCreateInfoINTEL
           forall a. Zero a => a
zero


-- | VkPerformanceMarkerInfoINTEL - Structure specifying performance markers
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdSetPerformanceMarkerINTEL'
data PerformanceMarkerInfoINTEL = PerformanceMarkerInfoINTEL
  { -- | @marker@ is the marker value that will be recorded into the opaque query
    -- results.
    PerformanceMarkerInfoINTEL -> Word64
marker :: Word64 }
  deriving (Typeable, PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
$c/= :: PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
== :: PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
$c== :: PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceMarkerInfoINTEL)
#endif
deriving instance Show PerformanceMarkerInfoINTEL

instance ToCStruct PerformanceMarkerInfoINTEL where
  withCStruct :: forall b.
PerformanceMarkerInfoINTEL
-> (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b)
-> IO b
withCStruct PerformanceMarkerInfoINTEL
x ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p PerformanceMarkerInfoINTEL
x (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b
f "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p)
  pokeCStruct :: forall b.
("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> PerformanceMarkerInfoINTEL -> IO b -> IO b
pokeCStruct "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p PerformanceMarkerInfoINTEL{Word64
marker :: Word64
$sel:marker:PerformanceMarkerInfoINTEL :: PerformanceMarkerInfoINTEL -> Word64
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
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 (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word64)) (Word64
marker)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b -> IO b
pokeZeroCStruct "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
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 (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
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 PerformanceMarkerInfoINTEL where
  peekCStruct :: ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> IO PerformanceMarkerInfoINTEL
peekCStruct "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p = do
    Word64
marker <- forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
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 -> PerformanceMarkerInfoINTEL
PerformanceMarkerInfoINTEL
             Word64
marker

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

instance Zero PerformanceMarkerInfoINTEL where
  zero :: PerformanceMarkerInfoINTEL
zero = Word64 -> PerformanceMarkerInfoINTEL
PerformanceMarkerInfoINTEL
           forall a. Zero a => a
zero


-- | VkPerformanceStreamMarkerInfoINTEL - Structure specifying stream
-- performance markers
--
-- == Valid Usage
--
-- -   #VUID-VkPerformanceStreamMarkerInfoINTEL-marker-02735# The value
--     written by the application into @marker@ /must/ only used the valid
--     bits as reported by 'getPerformanceParameterINTEL' with the
--     'PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkPerformanceStreamMarkerInfoINTEL-sType-sType# @sType@ /must/
--     be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL'
--
-- -   #VUID-VkPerformanceStreamMarkerInfoINTEL-pNext-pNext# @pNext@ /must/
--     be @NULL@
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdSetPerformanceStreamMarkerINTEL'
data PerformanceStreamMarkerInfoINTEL = PerformanceStreamMarkerInfoINTEL
  { -- | @marker@ is the marker value that will be recorded into the reports
    -- consumed by an external application.
    PerformanceStreamMarkerInfoINTEL -> Word32
marker :: Word32 }
  deriving (Typeable, PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
$c/= :: PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
== :: PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
$c== :: PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceStreamMarkerInfoINTEL)
#endif
deriving instance Show PerformanceStreamMarkerInfoINTEL

instance ToCStruct PerformanceStreamMarkerInfoINTEL where
  withCStruct :: forall b.
PerformanceStreamMarkerInfoINTEL
-> (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
    -> IO b)
-> IO b
withCStruct PerformanceStreamMarkerInfoINTEL
x ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p PerformanceStreamMarkerInfoINTEL
x (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL) -> IO b
f "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p)
  pokeCStruct :: forall b.
("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> PerformanceStreamMarkerInfoINTEL -> IO b -> IO b
pokeCStruct "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p PerformanceStreamMarkerInfoINTEL{Word32
marker :: Word32
$sel:marker:PerformanceStreamMarkerInfoINTEL :: PerformanceStreamMarkerInfoINTEL -> Word32
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
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 (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Word32
marker)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> IO b -> IO b
pokeZeroCStruct "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
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 (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (forall a. Zero a => a
zero)
    IO b
f

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

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

instance Zero PerformanceStreamMarkerInfoINTEL where
  zero :: PerformanceStreamMarkerInfoINTEL
zero = Word32 -> PerformanceStreamMarkerInfoINTEL
PerformanceStreamMarkerInfoINTEL
           forall a. Zero a => a
zero


-- | VkPerformanceOverrideInfoINTEL - Performance override information
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'PerformanceOverrideTypeINTEL',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdSetPerformanceOverrideINTEL'
data PerformanceOverrideInfoINTEL = PerformanceOverrideInfoINTEL
  { -- | @type@ is the particular 'PerformanceOverrideTypeINTEL' to set.
    --
    -- #VUID-VkPerformanceOverrideInfoINTEL-type-parameter# @type@ /must/ be a
    -- valid 'PerformanceOverrideTypeINTEL' value
    PerformanceOverrideInfoINTEL -> PerformanceOverrideTypeINTEL
type' :: PerformanceOverrideTypeINTEL
  , -- | @enable@ defines whether the override is enabled.
    PerformanceOverrideInfoINTEL -> Bool
enable :: Bool
  , -- | @parameter@ is a potential required parameter for the override.
    PerformanceOverrideInfoINTEL -> Word64
parameter :: Word64
  }
  deriving (Typeable, PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
$c/= :: PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
== :: PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
$c== :: PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceOverrideInfoINTEL)
#endif
deriving instance Show PerformanceOverrideInfoINTEL

instance ToCStruct PerformanceOverrideInfoINTEL where
  withCStruct :: forall b.
PerformanceOverrideInfoINTEL
-> (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO b)
-> IO b
withCStruct PerformanceOverrideInfoINTEL
x ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \"pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p PerformanceOverrideInfoINTEL
x (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO b
f "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p)
  pokeCStruct :: forall b.
("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> PerformanceOverrideInfoINTEL -> IO b -> IO b
pokeCStruct "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p PerformanceOverrideInfoINTEL{Bool
Word64
PerformanceOverrideTypeINTEL
parameter :: Word64
enable :: Bool
type' :: PerformanceOverrideTypeINTEL
$sel:parameter:PerformanceOverrideInfoINTEL :: PerformanceOverrideInfoINTEL -> Word64
$sel:enable:PerformanceOverrideInfoINTEL :: PerformanceOverrideInfoINTEL -> Bool
$sel:type':PerformanceOverrideInfoINTEL :: PerformanceOverrideInfoINTEL -> PerformanceOverrideTypeINTEL
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
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 (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PerformanceOverrideTypeINTEL)) (PerformanceOverrideTypeINTEL
type')
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
enable))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
parameter)
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO b -> IO b
pokeZeroCStruct "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
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 (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PerformanceOverrideTypeINTEL)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
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 (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
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 PerformanceOverrideInfoINTEL where
  peekCStruct :: ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO PerformanceOverrideInfoINTEL
peekCStruct "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p = do
    PerformanceOverrideTypeINTEL
type' <- forall a. Storable a => Ptr a -> IO a
peek @PerformanceOverrideTypeINTEL (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PerformanceOverrideTypeINTEL))
    Bool32
enable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32))
    Word64
parameter <- forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
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
$ PerformanceOverrideTypeINTEL
-> Bool -> Word64 -> PerformanceOverrideInfoINTEL
PerformanceOverrideInfoINTEL
             PerformanceOverrideTypeINTEL
type' (Bool32 -> Bool
bool32ToBool Bool32
enable) Word64
parameter

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

instance Zero PerformanceOverrideInfoINTEL where
  zero :: PerformanceOverrideInfoINTEL
zero = PerformanceOverrideTypeINTEL
-> Bool -> Word64 -> PerformanceOverrideInfoINTEL
PerformanceOverrideInfoINTEL
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkPerformanceConfigurationAcquireInfoINTEL - Acquire a configuration to
-- capture performance data
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'PerformanceConfigurationTypeINTEL',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'acquirePerformanceConfigurationINTEL'
data PerformanceConfigurationAcquireInfoINTEL = PerformanceConfigurationAcquireInfoINTEL
  { -- | @type@ is one of the 'PerformanceConfigurationTypeINTEL' type of
    -- performance configuration that will be acquired.
    --
    -- #VUID-VkPerformanceConfigurationAcquireInfoINTEL-type-parameter# @type@
    -- /must/ be a valid 'PerformanceConfigurationTypeINTEL' value
    PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationTypeINTEL
type' :: PerformanceConfigurationTypeINTEL }
  deriving (Typeable, PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
$c/= :: PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
== :: PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
$c== :: PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceConfigurationAcquireInfoINTEL)
#endif
deriving instance Show PerformanceConfigurationAcquireInfoINTEL

instance ToCStruct PerformanceConfigurationAcquireInfoINTEL where
  withCStruct :: forall b.
PerformanceConfigurationAcquireInfoINTEL
-> (("pAcquireInfo"
     ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
    -> IO b)
-> IO b
withCStruct PerformanceConfigurationAcquireInfoINTEL
x ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \"pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p PerformanceConfigurationAcquireInfoINTEL
x (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> IO b
f "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p)
  pokeCStruct :: forall b.
("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> PerformanceConfigurationAcquireInfoINTEL -> IO b -> IO b
pokeCStruct "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p PerformanceConfigurationAcquireInfoINTEL{PerformanceConfigurationTypeINTEL
type' :: PerformanceConfigurationTypeINTEL
$sel:type':PerformanceConfigurationAcquireInfoINTEL :: PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationTypeINTEL
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
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 (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PerformanceConfigurationTypeINTEL)) (PerformanceConfigurationTypeINTEL
type')
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> IO b -> IO b
pokeZeroCStruct "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
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 (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PerformanceConfigurationTypeINTEL)) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PerformanceConfigurationAcquireInfoINTEL where
  peekCStruct :: ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> IO PerformanceConfigurationAcquireInfoINTEL
peekCStruct "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p = do
    PerformanceConfigurationTypeINTEL
type' <- forall a. Storable a => Ptr a -> IO a
peek @PerformanceConfigurationTypeINTEL (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PerformanceConfigurationTypeINTEL))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationAcquireInfoINTEL
PerformanceConfigurationAcquireInfoINTEL
             PerformanceConfigurationTypeINTEL
type'

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

instance Zero PerformanceConfigurationAcquireInfoINTEL where
  zero :: PerformanceConfigurationAcquireInfoINTEL
zero = PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationAcquireInfoINTEL
PerformanceConfigurationAcquireInfoINTEL
           forall a. Zero a => a
zero


data PerformanceValueDataINTEL
  = Value32 Word32
  | Value64 Word64
  | ValueFloat Float
  | ValueBool Bool
  | ValueString ByteString
  deriving (Int -> PerformanceValueDataINTEL -> ShowS
[PerformanceValueDataINTEL] -> ShowS
PerformanceValueDataINTEL -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PerformanceValueDataINTEL] -> ShowS
$cshowList :: [PerformanceValueDataINTEL] -> ShowS
show :: PerformanceValueDataINTEL -> String
$cshow :: PerformanceValueDataINTEL -> String
showsPrec :: Int -> PerformanceValueDataINTEL -> ShowS
$cshowsPrec :: Int -> PerformanceValueDataINTEL -> ShowS
Show)

instance ToCStruct PerformanceValueDataINTEL where
  withCStruct :: forall b.
PerformanceValueDataINTEL
-> (Ptr PerformanceValueDataINTEL -> IO b) -> IO b
withCStruct PerformanceValueDataINTEL
x Ptr PerformanceValueDataINTEL -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
8 forall a b. (a -> b) -> a -> b
$ \Ptr PerformanceValueDataINTEL
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PerformanceValueDataINTEL
p PerformanceValueDataINTEL
x (Ptr PerformanceValueDataINTEL -> IO b
f Ptr PerformanceValueDataINTEL
p)
  pokeCStruct :: Ptr PerformanceValueDataINTEL -> PerformanceValueDataINTEL -> IO a -> IO a
  pokeCStruct :: forall b.
Ptr PerformanceValueDataINTEL
-> PerformanceValueDataINTEL -> IO b -> IO b
pokeCStruct Ptr PerformanceValueDataINTEL
p = (forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {k} (r :: k) (m :: k -> *) a.
ContT r m a -> (a -> m r) -> m r
runContT forall b c a. (b -> c) -> (a -> b) -> a -> c
.  \case
    Value32 Word32
v -> 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 -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr @_ @Word32 Ptr PerformanceValueDataINTEL
p) (Word32
v)
    Value64 Word64
v -> 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 -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr @_ @Word64 Ptr PerformanceValueDataINTEL
p) (Word64
v)
    ValueFloat Float
v -> 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 -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr @_ @CFloat Ptr PerformanceValueDataINTEL
p) (Float -> CFloat
CFloat (Float
v))
    ValueBool Bool
v -> 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 -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr @_ @Bool32 Ptr PerformanceValueDataINTEL
p) (Bool -> Bool32
boolToBool32 (Bool
v))
    ValueString ByteString
v -> do
      CString
valueString <- 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. ByteString -> (CString -> IO a) -> IO a
useAsCString (ByteString
v)
      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 -> a -> IO ()
poke (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr CChar) Ptr PerformanceValueDataINTEL
p) CString
valueString
  pokeZeroCStruct :: Ptr PerformanceValueDataINTEL -> IO b -> IO b
  pokeZeroCStruct :: forall b. Ptr PerformanceValueDataINTEL -> IO b -> IO b
pokeZeroCStruct Ptr PerformanceValueDataINTEL
_ IO b
f = IO b
f
  cStructSize :: Int
cStructSize = Int
8
  cStructAlignment :: Int
cStructAlignment = Int
8

instance Zero PerformanceValueDataINTEL where
  zero :: PerformanceValueDataINTEL
zero = Word64 -> PerformanceValueDataINTEL
Value64 forall a. Zero a => a
zero

peekPerformanceValueDataINTEL :: PerformanceValueTypeINTEL -> Ptr PerformanceValueDataINTEL -> IO PerformanceValueDataINTEL
peekPerformanceValueDataINTEL :: PerformanceValueTypeINTEL
-> Ptr PerformanceValueDataINTEL -> IO PerformanceValueDataINTEL
peekPerformanceValueDataINTEL PerformanceValueTypeINTEL
tag Ptr PerformanceValueDataINTEL
p = case PerformanceValueTypeINTEL
tag of
  PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_UINT32_INTEL -> Word32 -> PerformanceValueDataINTEL
Value32 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. Storable a => Ptr a -> IO a
peek @Word32 (forall a b. Ptr a -> Ptr b
castPtr @_ @Word32 Ptr PerformanceValueDataINTEL
p))
  PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_UINT64_INTEL -> Word64 -> PerformanceValueDataINTEL
Value64 forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall a. Storable a => Ptr a -> IO a
peek @Word64 (forall a b. Ptr a -> Ptr b
castPtr @_ @Word64 Ptr PerformanceValueDataINTEL
p))
  PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_FLOAT_INTEL -> Float -> PerformanceValueDataINTEL
ValueFloat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
    CFloat
valueFloat <- forall a. Storable a => Ptr a -> IO a
peek @CFloat (forall a b. Ptr a -> Ptr b
castPtr @_ @CFloat Ptr PerformanceValueDataINTEL
p)
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
valueFloat)
  PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_BOOL_INTEL -> Bool -> PerformanceValueDataINTEL
ValueBool forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
    Bool32
valueBool <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (forall a b. Ptr a -> Ptr b
castPtr @_ @Bool32 Ptr PerformanceValueDataINTEL
p)
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool32 -> Bool
bool32ToBool Bool32
valueBool)
  PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_STRING_INTEL -> ByteString -> PerformanceValueDataINTEL
ValueString forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CString -> IO ByteString
packCString forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Storable a => Ptr a -> IO a
peek (forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr CChar) Ptr PerformanceValueDataINTEL
p))


-- | VkPerformanceConfigurationTypeINTEL - Type of performance configuration
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'PerformanceConfigurationAcquireInfoINTEL'
newtype PerformanceConfigurationTypeINTEL = PerformanceConfigurationTypeINTEL Int32
  deriving newtype (PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c/= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
== :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c== :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
Eq, Eq PerformanceConfigurationTypeINTEL
PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Ordering
PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
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 :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
$cmin :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
max :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
$cmax :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
>= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c>= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
> :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c> :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
<= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c<= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
< :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c< :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
compare :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Ordering
$ccompare :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Ordering
Ord, Ptr PerformanceConfigurationTypeINTEL
-> IO PerformanceConfigurationTypeINTEL
Ptr PerformanceConfigurationTypeINTEL
-> Int -> IO PerformanceConfigurationTypeINTEL
Ptr PerformanceConfigurationTypeINTEL
-> Int -> PerformanceConfigurationTypeINTEL -> IO ()
Ptr PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> IO ()
PerformanceConfigurationTypeINTEL -> Int
forall b. Ptr b -> Int -> IO PerformanceConfigurationTypeINTEL
forall b.
Ptr b -> Int -> PerformanceConfigurationTypeINTEL -> 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 PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> IO ()
$cpoke :: Ptr PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> IO ()
peek :: Ptr PerformanceConfigurationTypeINTEL
-> IO PerformanceConfigurationTypeINTEL
$cpeek :: Ptr PerformanceConfigurationTypeINTEL
-> IO PerformanceConfigurationTypeINTEL
pokeByteOff :: forall b.
Ptr b -> Int -> PerformanceConfigurationTypeINTEL -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> PerformanceConfigurationTypeINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO PerformanceConfigurationTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceConfigurationTypeINTEL
pokeElemOff :: Ptr PerformanceConfigurationTypeINTEL
-> Int -> PerformanceConfigurationTypeINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceConfigurationTypeINTEL
-> Int -> PerformanceConfigurationTypeINTEL -> IO ()
peekElemOff :: Ptr PerformanceConfigurationTypeINTEL
-> Int -> IO PerformanceConfigurationTypeINTEL
$cpeekElemOff :: Ptr PerformanceConfigurationTypeINTEL
-> Int -> IO PerformanceConfigurationTypeINTEL
alignment :: PerformanceConfigurationTypeINTEL -> Int
$calignment :: PerformanceConfigurationTypeINTEL -> Int
sizeOf :: PerformanceConfigurationTypeINTEL -> Int
$csizeOf :: PerformanceConfigurationTypeINTEL -> Int
Storable, PerformanceConfigurationTypeINTEL
forall a. a -> Zero a
zero :: PerformanceConfigurationTypeINTEL
$czero :: PerformanceConfigurationTypeINTEL
Zero)

-- No documentation found for Nested "VkPerformanceConfigurationTypeINTEL" "VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL"
pattern $bPERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL :: PerformanceConfigurationTypeINTEL
$mPERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL :: forall {r}.
PerformanceConfigurationTypeINTEL
-> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL = PerformanceConfigurationTypeINTEL 0

{-# COMPLETE PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL :: PerformanceConfigurationTypeINTEL #-}

conNamePerformanceConfigurationTypeINTEL :: String
conNamePerformanceConfigurationTypeINTEL :: String
conNamePerformanceConfigurationTypeINTEL = String
"PerformanceConfigurationTypeINTEL"

enumPrefixPerformanceConfigurationTypeINTEL :: String
enumPrefixPerformanceConfigurationTypeINTEL :: String
enumPrefixPerformanceConfigurationTypeINTEL = String
"PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL"

showTablePerformanceConfigurationTypeINTEL :: [(PerformanceConfigurationTypeINTEL, String)]
showTablePerformanceConfigurationTypeINTEL :: [(PerformanceConfigurationTypeINTEL, String)]
showTablePerformanceConfigurationTypeINTEL =
  [
    ( PerformanceConfigurationTypeINTEL
PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL
    , String
""
    )
  ]

instance Show PerformanceConfigurationTypeINTEL where
  showsPrec :: Int -> PerformanceConfigurationTypeINTEL -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixPerformanceConfigurationTypeINTEL
      [(PerformanceConfigurationTypeINTEL, String)]
showTablePerformanceConfigurationTypeINTEL
      String
conNamePerformanceConfigurationTypeINTEL
      (\(PerformanceConfigurationTypeINTEL Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read PerformanceConfigurationTypeINTEL where
  readPrec :: ReadPrec PerformanceConfigurationTypeINTEL
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixPerformanceConfigurationTypeINTEL
      [(PerformanceConfigurationTypeINTEL, String)]
showTablePerformanceConfigurationTypeINTEL
      String
conNamePerformanceConfigurationTypeINTEL
      Int32 -> PerformanceConfigurationTypeINTEL
PerformanceConfigurationTypeINTEL

-- | VkQueryPoolSamplingModeINTEL - Enum specifying how performance queries
-- should be captured
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'QueryPoolPerformanceQueryCreateInfoINTEL'
newtype QueryPoolSamplingModeINTEL = QueryPoolSamplingModeINTEL Int32
  deriving newtype (QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c/= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
== :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c== :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
Eq, Eq QueryPoolSamplingModeINTEL
QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> Ordering
QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
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 :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
$cmin :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
max :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
$cmax :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
>= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c>= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
> :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c> :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
<= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c<= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
< :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c< :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
compare :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> Ordering
$ccompare :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> Ordering
Ord, Ptr QueryPoolSamplingModeINTEL -> IO QueryPoolSamplingModeINTEL
Ptr QueryPoolSamplingModeINTEL
-> Int -> IO QueryPoolSamplingModeINTEL
Ptr QueryPoolSamplingModeINTEL
-> Int -> QueryPoolSamplingModeINTEL -> IO ()
Ptr QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> IO ()
QueryPoolSamplingModeINTEL -> Int
forall b. Ptr b -> Int -> IO QueryPoolSamplingModeINTEL
forall b. Ptr b -> Int -> QueryPoolSamplingModeINTEL -> 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 QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> IO ()
$cpoke :: Ptr QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> IO ()
peek :: Ptr QueryPoolSamplingModeINTEL -> IO QueryPoolSamplingModeINTEL
$cpeek :: Ptr QueryPoolSamplingModeINTEL -> IO QueryPoolSamplingModeINTEL
pokeByteOff :: forall b. Ptr b -> Int -> QueryPoolSamplingModeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> QueryPoolSamplingModeINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO QueryPoolSamplingModeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO QueryPoolSamplingModeINTEL
pokeElemOff :: Ptr QueryPoolSamplingModeINTEL
-> Int -> QueryPoolSamplingModeINTEL -> IO ()
$cpokeElemOff :: Ptr QueryPoolSamplingModeINTEL
-> Int -> QueryPoolSamplingModeINTEL -> IO ()
peekElemOff :: Ptr QueryPoolSamplingModeINTEL
-> Int -> IO QueryPoolSamplingModeINTEL
$cpeekElemOff :: Ptr QueryPoolSamplingModeINTEL
-> Int -> IO QueryPoolSamplingModeINTEL
alignment :: QueryPoolSamplingModeINTEL -> Int
$calignment :: QueryPoolSamplingModeINTEL -> Int
sizeOf :: QueryPoolSamplingModeINTEL -> Int
$csizeOf :: QueryPoolSamplingModeINTEL -> Int
Storable, QueryPoolSamplingModeINTEL
forall a. a -> Zero a
zero :: QueryPoolSamplingModeINTEL
$czero :: QueryPoolSamplingModeINTEL
Zero)

-- | 'QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL' is the default mode in which the
-- application calls 'Vulkan.Core10.CommandBufferBuilding.cmdBeginQuery'
-- and 'Vulkan.Core10.CommandBufferBuilding.cmdEndQuery' to record
-- performance data.
pattern $bQUERY_POOL_SAMPLING_MODE_MANUAL_INTEL :: QueryPoolSamplingModeINTEL
$mQUERY_POOL_SAMPLING_MODE_MANUAL_INTEL :: forall {r}.
QueryPoolSamplingModeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL = QueryPoolSamplingModeINTEL 0

{-# COMPLETE QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL :: QueryPoolSamplingModeINTEL #-}

conNameQueryPoolSamplingModeINTEL :: String
conNameQueryPoolSamplingModeINTEL :: String
conNameQueryPoolSamplingModeINTEL = String
"QueryPoolSamplingModeINTEL"

enumPrefixQueryPoolSamplingModeINTEL :: String
enumPrefixQueryPoolSamplingModeINTEL :: String
enumPrefixQueryPoolSamplingModeINTEL = String
"QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL"

showTableQueryPoolSamplingModeINTEL :: [(QueryPoolSamplingModeINTEL, String)]
showTableQueryPoolSamplingModeINTEL :: [(QueryPoolSamplingModeINTEL, String)]
showTableQueryPoolSamplingModeINTEL =
  [
    ( QueryPoolSamplingModeINTEL
QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL
    , String
""
    )
  ]

instance Show QueryPoolSamplingModeINTEL where
  showsPrec :: Int -> QueryPoolSamplingModeINTEL -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixQueryPoolSamplingModeINTEL
      [(QueryPoolSamplingModeINTEL, String)]
showTableQueryPoolSamplingModeINTEL
      String
conNameQueryPoolSamplingModeINTEL
      (\(QueryPoolSamplingModeINTEL Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read QueryPoolSamplingModeINTEL where
  readPrec :: ReadPrec QueryPoolSamplingModeINTEL
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixQueryPoolSamplingModeINTEL
      [(QueryPoolSamplingModeINTEL, String)]
showTableQueryPoolSamplingModeINTEL
      String
conNameQueryPoolSamplingModeINTEL
      Int32 -> QueryPoolSamplingModeINTEL
QueryPoolSamplingModeINTEL

-- | VkPerformanceOverrideTypeINTEL - Performance override type
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'PerformanceOverrideInfoINTEL'
newtype PerformanceOverrideTypeINTEL = PerformanceOverrideTypeINTEL Int32
  deriving newtype (PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c/= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
== :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c== :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
Eq, Eq PerformanceOverrideTypeINTEL
PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Ordering
PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
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 :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
$cmin :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
max :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
$cmax :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
>= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c>= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
> :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c> :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
<= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c<= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
< :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c< :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
compare :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Ordering
$ccompare :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Ordering
Ord, Ptr PerformanceOverrideTypeINTEL -> IO PerformanceOverrideTypeINTEL
Ptr PerformanceOverrideTypeINTEL
-> Int -> IO PerformanceOverrideTypeINTEL
Ptr PerformanceOverrideTypeINTEL
-> Int -> PerformanceOverrideTypeINTEL -> IO ()
Ptr PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> IO ()
PerformanceOverrideTypeINTEL -> Int
forall b. Ptr b -> Int -> IO PerformanceOverrideTypeINTEL
forall b. Ptr b -> Int -> PerformanceOverrideTypeINTEL -> 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 PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> IO ()
$cpoke :: Ptr PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> IO ()
peek :: Ptr PerformanceOverrideTypeINTEL -> IO PerformanceOverrideTypeINTEL
$cpeek :: Ptr PerformanceOverrideTypeINTEL -> IO PerformanceOverrideTypeINTEL
pokeByteOff :: forall b. Ptr b -> Int -> PerformanceOverrideTypeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PerformanceOverrideTypeINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO PerformanceOverrideTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceOverrideTypeINTEL
pokeElemOff :: Ptr PerformanceOverrideTypeINTEL
-> Int -> PerformanceOverrideTypeINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceOverrideTypeINTEL
-> Int -> PerformanceOverrideTypeINTEL -> IO ()
peekElemOff :: Ptr PerformanceOverrideTypeINTEL
-> Int -> IO PerformanceOverrideTypeINTEL
$cpeekElemOff :: Ptr PerformanceOverrideTypeINTEL
-> Int -> IO PerformanceOverrideTypeINTEL
alignment :: PerformanceOverrideTypeINTEL -> Int
$calignment :: PerformanceOverrideTypeINTEL -> Int
sizeOf :: PerformanceOverrideTypeINTEL -> Int
$csizeOf :: PerformanceOverrideTypeINTEL -> Int
Storable, PerformanceOverrideTypeINTEL
forall a. a -> Zero a
zero :: PerformanceOverrideTypeINTEL
$czero :: PerformanceOverrideTypeINTEL
Zero)

-- | 'PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL' turns all rendering
-- operations into noop.
pattern $bPERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL :: PerformanceOverrideTypeINTEL
$mPERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL :: forall {r}.
PerformanceOverrideTypeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL = PerformanceOverrideTypeINTEL 0

-- | 'PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL' stalls the stream of
-- commands until all previously emitted commands have completed and all
-- caches been flushed and invalidated.
pattern $bPERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL :: PerformanceOverrideTypeINTEL
$mPERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL :: forall {r}.
PerformanceOverrideTypeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL = PerformanceOverrideTypeINTEL 1

{-# COMPLETE
  PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL
  , PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL ::
    PerformanceOverrideTypeINTEL
  #-}

conNamePerformanceOverrideTypeINTEL :: String
conNamePerformanceOverrideTypeINTEL :: String
conNamePerformanceOverrideTypeINTEL = String
"PerformanceOverrideTypeINTEL"

enumPrefixPerformanceOverrideTypeINTEL :: String
enumPrefixPerformanceOverrideTypeINTEL :: String
enumPrefixPerformanceOverrideTypeINTEL = String
"PERFORMANCE_OVERRIDE_TYPE_"

showTablePerformanceOverrideTypeINTEL :: [(PerformanceOverrideTypeINTEL, String)]
showTablePerformanceOverrideTypeINTEL :: [(PerformanceOverrideTypeINTEL, String)]
showTablePerformanceOverrideTypeINTEL =
  [
    ( PerformanceOverrideTypeINTEL
PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL
    , String
"NULL_HARDWARE_INTEL"
    )
  ,
    ( PerformanceOverrideTypeINTEL
PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL
    , String
"FLUSH_GPU_CACHES_INTEL"
    )
  ]

instance Show PerformanceOverrideTypeINTEL where
  showsPrec :: Int -> PerformanceOverrideTypeINTEL -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixPerformanceOverrideTypeINTEL
      [(PerformanceOverrideTypeINTEL, String)]
showTablePerformanceOverrideTypeINTEL
      String
conNamePerformanceOverrideTypeINTEL
      (\(PerformanceOverrideTypeINTEL Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read PerformanceOverrideTypeINTEL where
  readPrec :: ReadPrec PerformanceOverrideTypeINTEL
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixPerformanceOverrideTypeINTEL
      [(PerformanceOverrideTypeINTEL, String)]
showTablePerformanceOverrideTypeINTEL
      String
conNamePerformanceOverrideTypeINTEL
      Int32 -> PerformanceOverrideTypeINTEL
PerformanceOverrideTypeINTEL

-- | VkPerformanceParameterTypeINTEL - Parameters that can be queried
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'getPerformanceParameterINTEL'
newtype PerformanceParameterTypeINTEL = PerformanceParameterTypeINTEL Int32
  deriving newtype (PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c/= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
== :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c== :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
Eq, Eq PerformanceParameterTypeINTEL
PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Ordering
PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
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 :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
$cmin :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
max :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
$cmax :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
>= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c>= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
> :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c> :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
<= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c<= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
< :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c< :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
compare :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Ordering
$ccompare :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Ordering
Ord, Ptr PerformanceParameterTypeINTEL
-> IO PerformanceParameterTypeINTEL
Ptr PerformanceParameterTypeINTEL
-> Int -> IO PerformanceParameterTypeINTEL
Ptr PerformanceParameterTypeINTEL
-> Int -> PerformanceParameterTypeINTEL -> IO ()
Ptr PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> IO ()
PerformanceParameterTypeINTEL -> Int
forall b. Ptr b -> Int -> IO PerformanceParameterTypeINTEL
forall b. Ptr b -> Int -> PerformanceParameterTypeINTEL -> 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 PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> IO ()
$cpoke :: Ptr PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> IO ()
peek :: Ptr PerformanceParameterTypeINTEL
-> IO PerformanceParameterTypeINTEL
$cpeek :: Ptr PerformanceParameterTypeINTEL
-> IO PerformanceParameterTypeINTEL
pokeByteOff :: forall b. Ptr b -> Int -> PerformanceParameterTypeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PerformanceParameterTypeINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO PerformanceParameterTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceParameterTypeINTEL
pokeElemOff :: Ptr PerformanceParameterTypeINTEL
-> Int -> PerformanceParameterTypeINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceParameterTypeINTEL
-> Int -> PerformanceParameterTypeINTEL -> IO ()
peekElemOff :: Ptr PerformanceParameterTypeINTEL
-> Int -> IO PerformanceParameterTypeINTEL
$cpeekElemOff :: Ptr PerformanceParameterTypeINTEL
-> Int -> IO PerformanceParameterTypeINTEL
alignment :: PerformanceParameterTypeINTEL -> Int
$calignment :: PerformanceParameterTypeINTEL -> Int
sizeOf :: PerformanceParameterTypeINTEL -> Int
$csizeOf :: PerformanceParameterTypeINTEL -> Int
Storable, PerformanceParameterTypeINTEL
forall a. a -> Zero a
zero :: PerformanceParameterTypeINTEL
$czero :: PerformanceParameterTypeINTEL
Zero)

-- | 'PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL' has a boolean
-- result which tells whether hardware counters can be captured.
pattern $bPERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL :: PerformanceParameterTypeINTEL
$mPERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL :: forall {r}.
PerformanceParameterTypeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL = PerformanceParameterTypeINTEL 0

-- | 'PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL' has a 32
-- bits integer result which tells how many bits can be written into the
-- 'PerformanceValueINTEL' value.
pattern $bPERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL :: PerformanceParameterTypeINTEL
$mPERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL :: forall {r}.
PerformanceParameterTypeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL = PerformanceParameterTypeINTEL 1

{-# COMPLETE
  PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL
  , PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL ::
    PerformanceParameterTypeINTEL
  #-}

conNamePerformanceParameterTypeINTEL :: String
conNamePerformanceParameterTypeINTEL :: String
conNamePerformanceParameterTypeINTEL = String
"PerformanceParameterTypeINTEL"

enumPrefixPerformanceParameterTypeINTEL :: String
enumPrefixPerformanceParameterTypeINTEL :: String
enumPrefixPerformanceParameterTypeINTEL = String
"PERFORMANCE_PARAMETER_TYPE_"

showTablePerformanceParameterTypeINTEL :: [(PerformanceParameterTypeINTEL, String)]
showTablePerformanceParameterTypeINTEL :: [(PerformanceParameterTypeINTEL, String)]
showTablePerformanceParameterTypeINTEL =
  [
    ( PerformanceParameterTypeINTEL
PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL
    , String
"HW_COUNTERS_SUPPORTED_INTEL"
    )
  ,
    ( PerformanceParameterTypeINTEL
PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL
    , String
"STREAM_MARKER_VALID_BITS_INTEL"
    )
  ]

instance Show PerformanceParameterTypeINTEL where
  showsPrec :: Int -> PerformanceParameterTypeINTEL -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixPerformanceParameterTypeINTEL
      [(PerformanceParameterTypeINTEL, String)]
showTablePerformanceParameterTypeINTEL
      String
conNamePerformanceParameterTypeINTEL
      (\(PerformanceParameterTypeINTEL Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read PerformanceParameterTypeINTEL where
  readPrec :: ReadPrec PerformanceParameterTypeINTEL
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixPerformanceParameterTypeINTEL
      [(PerformanceParameterTypeINTEL, String)]
showTablePerformanceParameterTypeINTEL
      String
conNamePerformanceParameterTypeINTEL
      Int32 -> PerformanceParameterTypeINTEL
PerformanceParameterTypeINTEL

-- | VkPerformanceValueTypeINTEL - Type of the parameters that can be queried
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'PerformanceValueINTEL'
newtype PerformanceValueTypeINTEL = PerformanceValueTypeINTEL Int32
  deriving newtype (PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c/= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
== :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c== :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
Eq, Eq PerformanceValueTypeINTEL
PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Ordering
PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
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 :: PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
$cmin :: PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
max :: PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
$cmax :: PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
>= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c>= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
> :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c> :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
<= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c<= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
< :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c< :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
compare :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Ordering
$ccompare :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Ordering
Ord, Ptr PerformanceValueTypeINTEL -> IO PerformanceValueTypeINTEL
Ptr PerformanceValueTypeINTEL
-> Int -> IO PerformanceValueTypeINTEL
Ptr PerformanceValueTypeINTEL
-> Int -> PerformanceValueTypeINTEL -> IO ()
Ptr PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> IO ()
PerformanceValueTypeINTEL -> Int
forall b. Ptr b -> Int -> IO PerformanceValueTypeINTEL
forall b. Ptr b -> Int -> PerformanceValueTypeINTEL -> 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 PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> IO ()
$cpoke :: Ptr PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> IO ()
peek :: Ptr PerformanceValueTypeINTEL -> IO PerformanceValueTypeINTEL
$cpeek :: Ptr PerformanceValueTypeINTEL -> IO PerformanceValueTypeINTEL
pokeByteOff :: forall b. Ptr b -> Int -> PerformanceValueTypeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PerformanceValueTypeINTEL -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO PerformanceValueTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceValueTypeINTEL
pokeElemOff :: Ptr PerformanceValueTypeINTEL
-> Int -> PerformanceValueTypeINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceValueTypeINTEL
-> Int -> PerformanceValueTypeINTEL -> IO ()
peekElemOff :: Ptr PerformanceValueTypeINTEL
-> Int -> IO PerformanceValueTypeINTEL
$cpeekElemOff :: Ptr PerformanceValueTypeINTEL
-> Int -> IO PerformanceValueTypeINTEL
alignment :: PerformanceValueTypeINTEL -> Int
$calignment :: PerformanceValueTypeINTEL -> Int
sizeOf :: PerformanceValueTypeINTEL -> Int
$csizeOf :: PerformanceValueTypeINTEL -> Int
Storable, PerformanceValueTypeINTEL
forall a. a -> Zero a
zero :: PerformanceValueTypeINTEL
$czero :: PerformanceValueTypeINTEL
Zero)

-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_UINT32_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_UINT32_INTEL :: forall {r}.
PerformanceValueTypeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_VALUE_TYPE_UINT32_INTEL = PerformanceValueTypeINTEL 0

-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_UINT64_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_UINT64_INTEL :: forall {r}.
PerformanceValueTypeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_VALUE_TYPE_UINT64_INTEL = PerformanceValueTypeINTEL 1

-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_FLOAT_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_FLOAT_INTEL :: forall {r}.
PerformanceValueTypeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_VALUE_TYPE_FLOAT_INTEL = PerformanceValueTypeINTEL 2

-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_BOOL_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_BOOL_INTEL :: forall {r}.
PerformanceValueTypeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_VALUE_TYPE_BOOL_INTEL = PerformanceValueTypeINTEL 3

-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_STRING_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_STRING_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_STRING_INTEL :: forall {r}.
PerformanceValueTypeINTEL -> ((# #) -> r) -> ((# #) -> r) -> r
PERFORMANCE_VALUE_TYPE_STRING_INTEL = PerformanceValueTypeINTEL 4

{-# COMPLETE
  PERFORMANCE_VALUE_TYPE_UINT32_INTEL
  , PERFORMANCE_VALUE_TYPE_UINT64_INTEL
  , PERFORMANCE_VALUE_TYPE_FLOAT_INTEL
  , PERFORMANCE_VALUE_TYPE_BOOL_INTEL
  , PERFORMANCE_VALUE_TYPE_STRING_INTEL ::
    PerformanceValueTypeINTEL
  #-}

conNamePerformanceValueTypeINTEL :: String
conNamePerformanceValueTypeINTEL :: String
conNamePerformanceValueTypeINTEL = String
"PerformanceValueTypeINTEL"

enumPrefixPerformanceValueTypeINTEL :: String
enumPrefixPerformanceValueTypeINTEL :: String
enumPrefixPerformanceValueTypeINTEL = String
"PERFORMANCE_VALUE_TYPE_"

showTablePerformanceValueTypeINTEL :: [(PerformanceValueTypeINTEL, String)]
showTablePerformanceValueTypeINTEL :: [(PerformanceValueTypeINTEL, String)]
showTablePerformanceValueTypeINTEL =
  [
    ( PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_UINT32_INTEL
    , String
"UINT32_INTEL"
    )
  ,
    ( PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_UINT64_INTEL
    , String
"UINT64_INTEL"
    )
  ,
    ( PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_FLOAT_INTEL
    , String
"FLOAT_INTEL"
    )
  ,
    ( PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_BOOL_INTEL
    , String
"BOOL_INTEL"
    )
  ,
    ( PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_STRING_INTEL
    , String
"STRING_INTEL"
    )
  ]

instance Show PerformanceValueTypeINTEL where
  showsPrec :: Int -> PerformanceValueTypeINTEL -> ShowS
showsPrec =
    forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixPerformanceValueTypeINTEL
      [(PerformanceValueTypeINTEL, String)]
showTablePerformanceValueTypeINTEL
      String
conNamePerformanceValueTypeINTEL
      (\(PerformanceValueTypeINTEL Int32
x) -> Int32
x)
      (forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read PerformanceValueTypeINTEL where
  readPrec :: ReadPrec PerformanceValueTypeINTEL
readPrec =
    forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixPerformanceValueTypeINTEL
      [(PerformanceValueTypeINTEL, String)]
showTablePerformanceValueTypeINTEL
      String
conNamePerformanceValueTypeINTEL
      Int32 -> PerformanceValueTypeINTEL
PerformanceValueTypeINTEL

-- No documentation found for TopLevel "VkQueryPoolCreateInfoINTEL"
type QueryPoolCreateInfoINTEL = QueryPoolPerformanceQueryCreateInfoINTEL


type INTEL_PERFORMANCE_QUERY_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_INTEL_PERFORMANCE_QUERY_SPEC_VERSION"
pattern INTEL_PERFORMANCE_QUERY_SPEC_VERSION :: forall a . Integral a => a
pattern $bINTEL_PERFORMANCE_QUERY_SPEC_VERSION :: forall a. Integral a => a
$mINTEL_PERFORMANCE_QUERY_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
INTEL_PERFORMANCE_QUERY_SPEC_VERSION = 2


type INTEL_PERFORMANCE_QUERY_EXTENSION_NAME = "VK_INTEL_performance_query"

-- No documentation found for TopLevel "VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME"
pattern INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bINTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mINTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
INTEL_PERFORMANCE_QUERY_EXTENSION_NAME = "VK_INTEL_performance_query"