{-# OPTIONS_GHC -fno-warn-missing-pattern-synonym-signatures#-}
{-# OPTIONS_GHC -fno-warn-orphans#-}
{-# OPTIONS_HADDOCK not-home#-}
{-# LANGUAGE CPP                      #-}
{-# LANGUAGE DataKinds                #-}
{-# LANGUAGE FlexibleInstances        #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE MagicHash                #-}
{-# LANGUAGE PatternSynonyms          #-}
{-# LANGUAGE Strict                   #-}
{-# LANGUAGE TypeFamilies             #-}
{-# LANGUAGE ViewPatterns             #-}
module Graphics.Vulkan.Ext.VK_INTEL_performance_query
       (-- * Vulkan extension: @VK_INTEL_performance_query@
        -- |
        --
        -- supported: @vulkan@
        --
        -- contact: @Lionel Landwerlin @llandwerlin@
        --
        -- author: @INTEL@
        --
        -- type: @device@
        --
        -- Extension number: @211@
        module Graphics.Vulkan.Marshal, AHardwareBuffer(),
        ANativeWindow(), CAMetalLayer(), VkBool32(..), VkDeviceAddress(..),
        VkDeviceSize(..), VkFlags(..), VkSampleMask(..),
        VkInitializePerformanceApiInfoINTEL,
        VkPerformanceConfigurationAcquireInfoINTEL,
        VkPerformanceConfigurationTypeINTEL(..),
        VkPerformanceCounterDescriptionBitmaskKHR(..),
        VkPerformanceCounterScopeKHR(..),
        VkPerformanceCounterStorageKHR(..),
        VkPerformanceCounterUnitKHR(..),
        VkPerformanceOverrideTypeINTEL(..),
        VkPerformanceParameterTypeINTEL(..),
        VkPerformanceValueTypeINTEL(..),
        pattern VK_QUERY_SCOPE_COMMAND_BUFFER_KHR,
        pattern VK_QUERY_SCOPE_COMMAND_KHR,
        pattern VK_QUERY_SCOPE_RENDER_PASS_KHR,
        VkPerformanceCounterDescriptionFlagBitsKHR(),
        VkPerformanceCounterDescriptionFlagsKHR(),
        VkPerformanceMarkerInfoINTEL, VkPerformanceOverrideInfoINTEL,
        VkPerformanceStreamMarkerInfoINTEL, VkPerformanceValueDataINTEL,
        VkPerformanceValueINTEL, VkQueryControlBitmask(..),
        VkQueryPipelineStatisticBitmask(..),
        VkQueryPoolSamplingModeINTEL(..), VkQueryResultBitmask(..),
        VkQueryType(..), VkQueryControlFlagBits(), VkQueryControlFlags(),
        VkQueryPipelineStatisticFlagBits(),
        VkQueryPipelineStatisticFlags(), VkQueryPoolCreateFlagBits(..),
        VkQueryResultFlagBits(), VkQueryResultFlags(),
        VkAndroidSurfaceCreateFlagsKHR(..), VkBufferViewCreateFlags(..),
        VkBuildAccelerationStructureFlagsNV(..),
        VkCommandPoolTrimFlags(..), VkCommandPoolTrimFlagsKHR(..),
        VkDebugUtilsMessengerCallbackDataFlagsEXT(..),
        VkDebugUtilsMessengerCreateFlagsEXT(..),
        VkDescriptorBindingFlagsEXT(..), VkDescriptorPoolResetFlags(..),
        VkDescriptorUpdateTemplateCreateFlags(..),
        VkDescriptorUpdateTemplateCreateFlagsKHR(..),
        VkDeviceCreateFlags(..), VkDirectFBSurfaceCreateFlagsEXT(..),
        VkDisplayModeCreateFlagsKHR(..),
        VkDisplaySurfaceCreateFlagsKHR(..), VkEventCreateFlags(..),
        VkExternalFenceFeatureFlagsKHR(..),
        VkExternalFenceHandleTypeFlagsKHR(..),
        VkExternalMemoryFeatureFlagsKHR(..),
        VkExternalMemoryHandleTypeFlagsKHR(..),
        VkExternalSemaphoreFeatureFlagsKHR(..),
        VkExternalSemaphoreHandleTypeFlagsKHR(..),
        VkFenceImportFlagsKHR(..), VkGeometryFlagsNV(..),
        VkGeometryInstanceFlagsNV(..), VkHeadlessSurfaceCreateFlagsEXT(..),
        VkIOSSurfaceCreateFlagsMVK(..),
        VkImagePipeSurfaceCreateFlagsFUCHSIA(..),
        VkInstanceCreateFlags(..), VkMacOSSurfaceCreateFlagsMVK(..),
        VkMemoryAllocateFlagsKHR(..), VkMemoryMapFlags(..),
        VkMetalSurfaceCreateFlagsEXT(..), VkPeerMemoryFeatureFlagsKHR(..),
        VkPipelineColorBlendStateCreateFlags(..),
        VkPipelineCoverageModulationStateCreateFlagsNV(..),
        VkPipelineCoverageReductionStateCreateFlagsNV(..),
        VkPipelineCoverageToColorStateCreateFlagsNV(..),
        VkPipelineDepthStencilStateCreateFlags(..),
        VkPipelineDiscardRectangleStateCreateFlagsEXT(..),
        VkPipelineDynamicStateCreateFlags(..),
        VkPipelineInputAssemblyStateCreateFlags(..),
        VkPipelineLayoutCreateFlags(..),
        VkPipelineMultisampleStateCreateFlags(..),
        VkPipelineRasterizationConservativeStateCreateFlagsEXT(..),
        VkPipelineRasterizationDepthClipStateCreateFlagsEXT(..),
        VkPipelineRasterizationStateCreateFlags(..),
        VkPipelineRasterizationStateStreamCreateFlagsEXT(..),
        VkPipelineTessellationStateCreateFlags(..),
        VkPipelineVertexInputStateCreateFlags(..),
        VkPipelineViewportStateCreateFlags(..),
        VkPipelineViewportSwizzleStateCreateFlagsNV(..),
        VkQueryPoolCreateFlags(..), VkResolveModeFlagsKHR(..),
        VkSemaphoreCreateFlags(..), VkSemaphoreImportFlagsKHR(..),
        VkSemaphoreWaitFlagsKHR(..),
        VkStreamDescriptorSurfaceCreateFlagsGGP(..),
        VkValidationCacheCreateFlagsEXT(..), VkViSurfaceCreateFlagsNN(..),
        VkWaylandSurfaceCreateFlagsKHR(..),
        VkWin32SurfaceCreateFlagsKHR(..), VkXcbSurfaceCreateFlagsKHR(..),
        VkXlibSurfaceCreateFlagsKHR(..), VkQueryPoolCreateInfo,
        VkQueryPoolCreateInfoINTEL,
        VkQueryPoolPerformanceQueryCreateInfoINTEL, VkStructureType(..),
        -- > #include "vk_platform.h"
        VkInitializePerformanceApiINTEL,
        pattern VkInitializePerformanceApiINTEL,
        HS_vkInitializePerformanceApiINTEL,
        PFN_vkInitializePerformanceApiINTEL,
        VkUninitializePerformanceApiINTEL,
        pattern VkUninitializePerformanceApiINTEL,
        HS_vkUninitializePerformanceApiINTEL,
        PFN_vkUninitializePerformanceApiINTEL,
        VkCmdSetPerformanceMarkerINTEL,
        pattern VkCmdSetPerformanceMarkerINTEL,
        HS_vkCmdSetPerformanceMarkerINTEL,
        PFN_vkCmdSetPerformanceMarkerINTEL,
        VkCmdSetPerformanceStreamMarkerINTEL,
        pattern VkCmdSetPerformanceStreamMarkerINTEL,
        HS_vkCmdSetPerformanceStreamMarkerINTEL,
        PFN_vkCmdSetPerformanceStreamMarkerINTEL,
        VkCmdSetPerformanceOverrideINTEL,
        pattern VkCmdSetPerformanceOverrideINTEL,
        HS_vkCmdSetPerformanceOverrideINTEL,
        PFN_vkCmdSetPerformanceOverrideINTEL,
        VkAcquirePerformanceConfigurationINTEL,
        pattern VkAcquirePerformanceConfigurationINTEL,
        HS_vkAcquirePerformanceConfigurationINTEL,
        PFN_vkAcquirePerformanceConfigurationINTEL,
        VkReleasePerformanceConfigurationINTEL,
        pattern VkReleasePerformanceConfigurationINTEL,
        HS_vkReleasePerformanceConfigurationINTEL,
        PFN_vkReleasePerformanceConfigurationINTEL,
        VkQueueSetPerformanceConfigurationINTEL,
        pattern VkQueueSetPerformanceConfigurationINTEL,
        HS_vkQueueSetPerformanceConfigurationINTEL,
        PFN_vkQueueSetPerformanceConfigurationINTEL,
        VkGetPerformanceParameterINTEL,
        pattern VkGetPerformanceParameterINTEL,
        HS_vkGetPerformanceParameterINTEL,
        PFN_vkGetPerformanceParameterINTEL, VkResult(..),
        VkAccelerationStructureKHR, VkAccelerationStructureKHR_T(),
        VkAccelerationStructureNV, VkAccelerationStructureNV_T(), VkBuffer,
        VkBufferView, VkBufferView_T(), VkBuffer_T(), VkCommandBuffer,
        VkCommandBuffer_T(), VkCommandPool, VkCommandPool_T(),
        VkDebugReportCallbackEXT, VkDebugReportCallbackEXT_T(),
        VkDebugUtilsMessengerEXT, VkDebugUtilsMessengerEXT_T(),
        VkDeferredOperationKHR, VkDeferredOperationKHR_T(),
        VkDescriptorPool, VkDescriptorPool_T(), VkDescriptorSet,
        VkDescriptorSetLayout, VkDescriptorSetLayout_T(),
        VkDescriptorSet_T(), VkDescriptorUpdateTemplate,
        VkDescriptorUpdateTemplateKHR, VkDescriptorUpdateTemplateKHR_T(),
        VkDescriptorUpdateTemplate_T(), VkDevice, VkDeviceMemory,
        VkDeviceMemory_T(), VkDevice_T(), VkDisplayKHR, VkDisplayKHR_T(),
        VkDisplayModeKHR, VkDisplayModeKHR_T(), VkEvent, VkEvent_T(),
        VkFence, VkFence_T(), VkFramebuffer, VkFramebuffer_T(), VkImage,
        VkImageView, VkImageView_T(), VkImage_T(),
        VkIndirectCommandsLayoutNV, VkIndirectCommandsLayoutNV_T(),
        VkInstance, VkInstance_T(), VkPerformanceConfigurationINTEL,
        VkPerformanceConfigurationINTEL_T(), VkPhysicalDevice,
        VkPhysicalDevice_T(), VkPipeline, VkPipelineCache,
        VkPipelineCache_T(), VkPipelineLayout, VkPipelineLayout_T(),
        VkPipeline_T(), VkPrivateDataSlotEXT, VkPrivateDataSlotEXT_T(),
        VkQueryPool, VkQueryPool_T(), VkQueue, VkQueue_T(), VkRenderPass,
        VkRenderPass_T(), VkSampler, VkSamplerYcbcrConversion,
        VkSamplerYcbcrConversionKHR, VkSamplerYcbcrConversionKHR_T(),
        VkSamplerYcbcrConversion_T(), VkSampler_T(), VkSemaphore,
        VkSemaphore_T(), VkShaderModule, VkShaderModule_T(), VkSurfaceKHR,
        VkSurfaceKHR_T(), VkSwapchainKHR, VkSwapchainKHR_T(),
        VkValidationCacheEXT, VkValidationCacheEXT_T(),
        VkPerformanceCounterDescriptionKHR, VkPerformanceCounterKHR,
        VkPerformanceCounterResultKHR, VkPerformanceQuerySubmitInfoKHR,
        VK_INTEL_PERFORMANCE_QUERY_SPEC_VERSION,
        pattern VK_INTEL_PERFORMANCE_QUERY_SPEC_VERSION,
        VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME,
        pattern VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME,
        pattern VK_STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL,
        pattern VK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL,
        pattern VK_STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL,
        pattern VK_STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL,
        pattern VK_STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL,
        pattern VK_STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL,
        pattern VK_STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL,
        pattern VK_QUERY_TYPE_PERFORMANCE_QUERY_INTEL,
        pattern VK_OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL)
       where
import GHC.Ptr                                                        (Ptr (..))
import Graphics.Vulkan.Marshal
import Graphics.Vulkan.Marshal.Proc                                   (VulkanProc (..))
import Graphics.Vulkan.Types.BaseTypes
import Graphics.Vulkan.Types.Bitmasks
import Graphics.Vulkan.Types.Enum.ObjectType                          (VkObjectType (..))
import Graphics.Vulkan.Types.Enum.Performance
import Graphics.Vulkan.Types.Enum.Query
import Graphics.Vulkan.Types.Enum.Result
import Graphics.Vulkan.Types.Enum.StructureType
import Graphics.Vulkan.Types.Handles
import Graphics.Vulkan.Types.Struct.InitializePerformanceApiInfoINTEL
import Graphics.Vulkan.Types.Struct.Performance
import Graphics.Vulkan.Types.Struct.QueryPool                         (VkQueryPoolCreateInfo,
                                                                       VkQueryPoolCreateInfoINTEL,
                                                                       VkQueryPoolPerformanceQueryCreateInfoINTEL)

pattern VkInitializePerformanceApiINTEL :: CString

pattern $bVkInitializePerformanceApiINTEL :: CString
$mVkInitializePerformanceApiINTEL :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkInitializePerformanceApiINTEL <-
        (is_VkInitializePerformanceApiINTEL -> True)
  where
    VkInitializePerformanceApiINTEL = CString
_VkInitializePerformanceApiINTEL

{-# INLINE _VkInitializePerformanceApiINTEL #-}

_VkInitializePerformanceApiINTEL :: CString
_VkInitializePerformanceApiINTEL :: CString
_VkInitializePerformanceApiINTEL
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkInitializePerformanceApiINTEL\NUL"#

{-# INLINE is_VkInitializePerformanceApiINTEL #-}

is_VkInitializePerformanceApiINTEL :: CString -> Bool
is_VkInitializePerformanceApiINTEL :: CString -> Bool
is_VkInitializePerformanceApiINTEL
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VkInitializePerformanceApiINTEL

type VkInitializePerformanceApiINTEL =
     "vkInitializePerformanceApiINTEL"

-- | Success codes: 'VK_SUCCESS'.
--
--   Error codes: 'VK_ERROR_TOO_MANY_OBJECTS', 'VK_ERROR_OUT_OF_HOST_MEMORY'.
--
--   > VkResult vkInitializePerformanceApiINTEL
--   >     ( VkDevice device
--   >     , const VkInitializePerformanceApiInfoINTEL* pInitializeInfo
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkInitializePerformanceApiINTEL vkInitializePerformanceApiINTEL registry at www.khronos.org>
type HS_vkInitializePerformanceApiINTEL =
     VkDevice -- ^ device
              -> Ptr VkInitializePerformanceApiInfoINTEL -- ^ pInitializeInfo
                                                         -> IO VkResult

type PFN_vkInitializePerformanceApiINTEL =
     FunPtr HS_vkInitializePerformanceApiINTEL

foreign import ccall unsafe "dynamic"
               unwrapVkInitializePerformanceApiINTELUnsafe ::
               PFN_vkInitializePerformanceApiINTEL ->
                 HS_vkInitializePerformanceApiINTEL

foreign import ccall safe "dynamic"
               unwrapVkInitializePerformanceApiINTELSafe ::
               PFN_vkInitializePerformanceApiINTEL ->
                 HS_vkInitializePerformanceApiINTEL

instance VulkanProc "vkInitializePerformanceApiINTEL" where
    type VkProcType "vkInitializePerformanceApiINTEL" =
         HS_vkInitializePerformanceApiINTEL
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkInitializePerformanceApiINTEL

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkInitializePerformanceApiINTEL")
-> VkProcType "vkInitializePerformanceApiINTEL"
unwrapVkProcPtrUnsafe = FunPtr (VkProcType "vkInitializePerformanceApiINTEL")
-> VkProcType "vkInitializePerformanceApiINTEL"
PFN_vkInitializePerformanceApiINTEL
-> HS_vkInitializePerformanceApiINTEL
unwrapVkInitializePerformanceApiINTELUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkInitializePerformanceApiINTEL")
-> VkProcType "vkInitializePerformanceApiINTEL"
unwrapVkProcPtrSafe = FunPtr (VkProcType "vkInitializePerformanceApiINTEL")
-> VkProcType "vkInitializePerformanceApiINTEL"
PFN_vkInitializePerformanceApiINTEL
-> HS_vkInitializePerformanceApiINTEL
unwrapVkInitializePerformanceApiINTELSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkUninitializePerformanceApiINTEL :: CString

pattern $bVkUninitializePerformanceApiINTEL :: CString
$mVkUninitializePerformanceApiINTEL :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkUninitializePerformanceApiINTEL <-
        (is_VkUninitializePerformanceApiINTEL -> True)
  where
    VkUninitializePerformanceApiINTEL
      = CString
_VkUninitializePerformanceApiINTEL

{-# INLINE _VkUninitializePerformanceApiINTEL #-}

_VkUninitializePerformanceApiINTEL :: CString
_VkUninitializePerformanceApiINTEL :: CString
_VkUninitializePerformanceApiINTEL
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkUninitializePerformanceApiINTEL\NUL"#

{-# INLINE is_VkUninitializePerformanceApiINTEL #-}

is_VkUninitializePerformanceApiINTEL :: CString -> Bool
is_VkUninitializePerformanceApiINTEL :: CString -> Bool
is_VkUninitializePerformanceApiINTEL
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VkUninitializePerformanceApiINTEL

type VkUninitializePerformanceApiINTEL =
     "vkUninitializePerformanceApiINTEL"

-- | > void vkUninitializePerformanceApiINTEL
--   >     ( VkDevice device
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkUninitializePerformanceApiINTEL vkUninitializePerformanceApiINTEL registry at www.khronos.org>
type HS_vkUninitializePerformanceApiINTEL = VkDevice -- ^ device
                                                     -> IO ()

type PFN_vkUninitializePerformanceApiINTEL =
     FunPtr HS_vkUninitializePerformanceApiINTEL

foreign import ccall unsafe "dynamic"
               unwrapVkUninitializePerformanceApiINTELUnsafe ::
               PFN_vkUninitializePerformanceApiINTEL ->
                 HS_vkUninitializePerformanceApiINTEL

foreign import ccall safe "dynamic"
               unwrapVkUninitializePerformanceApiINTELSafe ::
               PFN_vkUninitializePerformanceApiINTEL ->
                 HS_vkUninitializePerformanceApiINTEL

instance VulkanProc "vkUninitializePerformanceApiINTEL" where
    type VkProcType "vkUninitializePerformanceApiINTEL" =
         HS_vkUninitializePerformanceApiINTEL
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkUninitializePerformanceApiINTEL

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkUninitializePerformanceApiINTEL")
-> VkProcType "vkUninitializePerformanceApiINTEL"
unwrapVkProcPtrUnsafe
      = FunPtr (VkProcType "vkUninitializePerformanceApiINTEL")
-> VkProcType "vkUninitializePerformanceApiINTEL"
PFN_vkUninitializePerformanceApiINTEL
-> HS_vkUninitializePerformanceApiINTEL
unwrapVkUninitializePerformanceApiINTELUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkUninitializePerformanceApiINTEL")
-> VkProcType "vkUninitializePerformanceApiINTEL"
unwrapVkProcPtrSafe = FunPtr (VkProcType "vkUninitializePerformanceApiINTEL")
-> VkProcType "vkUninitializePerformanceApiINTEL"
PFN_vkUninitializePerformanceApiINTEL
-> HS_vkUninitializePerformanceApiINTEL
unwrapVkUninitializePerformanceApiINTELSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkCmdSetPerformanceMarkerINTEL :: CString

pattern $bVkCmdSetPerformanceMarkerINTEL :: CString
$mVkCmdSetPerformanceMarkerINTEL :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkCmdSetPerformanceMarkerINTEL <-
        (is_VkCmdSetPerformanceMarkerINTEL -> True)
  where
    VkCmdSetPerformanceMarkerINTEL = CString
_VkCmdSetPerformanceMarkerINTEL

{-# INLINE _VkCmdSetPerformanceMarkerINTEL #-}

_VkCmdSetPerformanceMarkerINTEL :: CString
_VkCmdSetPerformanceMarkerINTEL :: CString
_VkCmdSetPerformanceMarkerINTEL
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkCmdSetPerformanceMarkerINTEL\NUL"#

{-# INLINE is_VkCmdSetPerformanceMarkerINTEL #-}

is_VkCmdSetPerformanceMarkerINTEL :: CString -> Bool
is_VkCmdSetPerformanceMarkerINTEL :: CString -> Bool
is_VkCmdSetPerformanceMarkerINTEL
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VkCmdSetPerformanceMarkerINTEL

type VkCmdSetPerformanceMarkerINTEL =
     "vkCmdSetPerformanceMarkerINTEL"

-- | Success codes: 'VK_SUCCESS'.
--
--   Error codes: 'VK_ERROR_TOO_MANY_OBJECTS', 'VK_ERROR_OUT_OF_HOST_MEMORY'.
--
--   Queues: 'graphics', 'compute', 'transfer'.
--
--   Renderpass: @both@
--
--   > VkResult vkCmdSetPerformanceMarkerINTEL
--   >     ( VkCommandBuffer commandBuffer
--   >     , const VkPerformanceMarkerInfoINTEL* pMarkerInfo
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdSetPerformanceMarkerINTEL vkCmdSetPerformanceMarkerINTEL registry at www.khronos.org>
type HS_vkCmdSetPerformanceMarkerINTEL =
     VkCommandBuffer -- ^ commandBuffer
                     -> Ptr VkPerformanceMarkerInfoINTEL -- ^ pMarkerInfo
                                                         -> IO VkResult

type PFN_vkCmdSetPerformanceMarkerINTEL =
     FunPtr HS_vkCmdSetPerformanceMarkerINTEL

foreign import ccall unsafe "dynamic"
               unwrapVkCmdSetPerformanceMarkerINTELUnsafe ::
               PFN_vkCmdSetPerformanceMarkerINTEL ->
                 HS_vkCmdSetPerformanceMarkerINTEL

foreign import ccall safe "dynamic"
               unwrapVkCmdSetPerformanceMarkerINTELSafe ::
               PFN_vkCmdSetPerformanceMarkerINTEL ->
                 HS_vkCmdSetPerformanceMarkerINTEL

instance VulkanProc "vkCmdSetPerformanceMarkerINTEL" where
    type VkProcType "vkCmdSetPerformanceMarkerINTEL" =
         HS_vkCmdSetPerformanceMarkerINTEL
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkCmdSetPerformanceMarkerINTEL

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCmdSetPerformanceMarkerINTEL")
-> VkProcType "vkCmdSetPerformanceMarkerINTEL"
unwrapVkProcPtrUnsafe = FunPtr (VkProcType "vkCmdSetPerformanceMarkerINTEL")
-> VkProcType "vkCmdSetPerformanceMarkerINTEL"
PFN_vkCmdSetPerformanceMarkerINTEL
-> HS_vkCmdSetPerformanceMarkerINTEL
unwrapVkCmdSetPerformanceMarkerINTELUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCmdSetPerformanceMarkerINTEL")
-> VkProcType "vkCmdSetPerformanceMarkerINTEL"
unwrapVkProcPtrSafe = FunPtr (VkProcType "vkCmdSetPerformanceMarkerINTEL")
-> VkProcType "vkCmdSetPerformanceMarkerINTEL"
PFN_vkCmdSetPerformanceMarkerINTEL
-> HS_vkCmdSetPerformanceMarkerINTEL
unwrapVkCmdSetPerformanceMarkerINTELSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkCmdSetPerformanceStreamMarkerINTEL :: CString

pattern $bVkCmdSetPerformanceStreamMarkerINTEL :: CString
$mVkCmdSetPerformanceStreamMarkerINTEL :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkCmdSetPerformanceStreamMarkerINTEL <-
        (is_VkCmdSetPerformanceStreamMarkerINTEL -> True)
  where
    VkCmdSetPerformanceStreamMarkerINTEL
      = CString
_VkCmdSetPerformanceStreamMarkerINTEL

{-# INLINE _VkCmdSetPerformanceStreamMarkerINTEL #-}

_VkCmdSetPerformanceStreamMarkerINTEL :: CString
_VkCmdSetPerformanceStreamMarkerINTEL :: CString
_VkCmdSetPerformanceStreamMarkerINTEL
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkCmdSetPerformanceStreamMarkerINTEL\NUL"#

{-# INLINE is_VkCmdSetPerformanceStreamMarkerINTEL #-}

is_VkCmdSetPerformanceStreamMarkerINTEL :: CString -> Bool
is_VkCmdSetPerformanceStreamMarkerINTEL :: CString -> Bool
is_VkCmdSetPerformanceStreamMarkerINTEL
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VkCmdSetPerformanceStreamMarkerINTEL

type VkCmdSetPerformanceStreamMarkerINTEL =
     "vkCmdSetPerformanceStreamMarkerINTEL"

-- | Success codes: 'VK_SUCCESS'.
--
--   Error codes: 'VK_ERROR_TOO_MANY_OBJECTS', 'VK_ERROR_OUT_OF_HOST_MEMORY'.
--
--   Queues: 'graphics', 'compute', 'transfer'.
--
--   Renderpass: @both@
--
--   > VkResult vkCmdSetPerformanceStreamMarkerINTEL
--   >     ( VkCommandBuffer commandBuffer
--   >     , const VkPerformanceStreamMarkerInfoINTEL* pMarkerInfo
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdSetPerformanceStreamMarkerINTEL vkCmdSetPerformanceStreamMarkerINTEL registry at www.khronos.org>
type HS_vkCmdSetPerformanceStreamMarkerINTEL =
     VkCommandBuffer -- ^ commandBuffer
                     ->
       Ptr VkPerformanceStreamMarkerInfoINTEL -- ^ pMarkerInfo
                                              -> IO VkResult

type PFN_vkCmdSetPerformanceStreamMarkerINTEL =
     FunPtr HS_vkCmdSetPerformanceStreamMarkerINTEL

foreign import ccall unsafe "dynamic"
               unwrapVkCmdSetPerformanceStreamMarkerINTELUnsafe ::
               PFN_vkCmdSetPerformanceStreamMarkerINTEL ->
                 HS_vkCmdSetPerformanceStreamMarkerINTEL

foreign import ccall safe "dynamic"
               unwrapVkCmdSetPerformanceStreamMarkerINTELSafe ::
               PFN_vkCmdSetPerformanceStreamMarkerINTEL ->
                 HS_vkCmdSetPerformanceStreamMarkerINTEL

instance VulkanProc "vkCmdSetPerformanceStreamMarkerINTEL" where
    type VkProcType "vkCmdSetPerformanceStreamMarkerINTEL" =
         HS_vkCmdSetPerformanceStreamMarkerINTEL
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkCmdSetPerformanceStreamMarkerINTEL

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCmdSetPerformanceStreamMarkerINTEL")
-> VkProcType "vkCmdSetPerformanceStreamMarkerINTEL"
unwrapVkProcPtrUnsafe
      = FunPtr (VkProcType "vkCmdSetPerformanceStreamMarkerINTEL")
-> VkProcType "vkCmdSetPerformanceStreamMarkerINTEL"
PFN_vkCmdSetPerformanceStreamMarkerINTEL
-> HS_vkCmdSetPerformanceStreamMarkerINTEL
unwrapVkCmdSetPerformanceStreamMarkerINTELUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCmdSetPerformanceStreamMarkerINTEL")
-> VkProcType "vkCmdSetPerformanceStreamMarkerINTEL"
unwrapVkProcPtrSafe
      = FunPtr (VkProcType "vkCmdSetPerformanceStreamMarkerINTEL")
-> VkProcType "vkCmdSetPerformanceStreamMarkerINTEL"
PFN_vkCmdSetPerformanceStreamMarkerINTEL
-> HS_vkCmdSetPerformanceStreamMarkerINTEL
unwrapVkCmdSetPerformanceStreamMarkerINTELSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkCmdSetPerformanceOverrideINTEL :: CString

pattern $bVkCmdSetPerformanceOverrideINTEL :: CString
$mVkCmdSetPerformanceOverrideINTEL :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkCmdSetPerformanceOverrideINTEL <-
        (is_VkCmdSetPerformanceOverrideINTEL -> True)
  where
    VkCmdSetPerformanceOverrideINTEL
      = CString
_VkCmdSetPerformanceOverrideINTEL

{-# INLINE _VkCmdSetPerformanceOverrideINTEL #-}

_VkCmdSetPerformanceOverrideINTEL :: CString
_VkCmdSetPerformanceOverrideINTEL :: CString
_VkCmdSetPerformanceOverrideINTEL
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkCmdSetPerformanceOverrideINTEL\NUL"#

{-# INLINE is_VkCmdSetPerformanceOverrideINTEL #-}

is_VkCmdSetPerformanceOverrideINTEL :: CString -> Bool
is_VkCmdSetPerformanceOverrideINTEL :: CString -> Bool
is_VkCmdSetPerformanceOverrideINTEL
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VkCmdSetPerformanceOverrideINTEL

type VkCmdSetPerformanceOverrideINTEL =
     "vkCmdSetPerformanceOverrideINTEL"

-- | Success codes: 'VK_SUCCESS'.
--
--   Error codes: 'VK_ERROR_TOO_MANY_OBJECTS', 'VK_ERROR_OUT_OF_HOST_MEMORY'.
--
--   Queues: 'graphics', 'compute', 'transfer'.
--
--   Renderpass: @both@
--
--   > VkResult vkCmdSetPerformanceOverrideINTEL
--   >     ( VkCommandBuffer commandBuffer
--   >     , const VkPerformanceOverrideInfoINTEL* pOverrideInfo
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdSetPerformanceOverrideINTEL vkCmdSetPerformanceOverrideINTEL registry at www.khronos.org>
type HS_vkCmdSetPerformanceOverrideINTEL =
     VkCommandBuffer -- ^ commandBuffer
                     ->
       Ptr VkPerformanceOverrideInfoINTEL -- ^ pOverrideInfo
                                          -> IO VkResult

type PFN_vkCmdSetPerformanceOverrideINTEL =
     FunPtr HS_vkCmdSetPerformanceOverrideINTEL

foreign import ccall unsafe "dynamic"
               unwrapVkCmdSetPerformanceOverrideINTELUnsafe ::
               PFN_vkCmdSetPerformanceOverrideINTEL ->
                 HS_vkCmdSetPerformanceOverrideINTEL

foreign import ccall safe "dynamic"
               unwrapVkCmdSetPerformanceOverrideINTELSafe ::
               PFN_vkCmdSetPerformanceOverrideINTEL ->
                 HS_vkCmdSetPerformanceOverrideINTEL

instance VulkanProc "vkCmdSetPerformanceOverrideINTEL" where
    type VkProcType "vkCmdSetPerformanceOverrideINTEL" =
         HS_vkCmdSetPerformanceOverrideINTEL
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkCmdSetPerformanceOverrideINTEL

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCmdSetPerformanceOverrideINTEL")
-> VkProcType "vkCmdSetPerformanceOverrideINTEL"
unwrapVkProcPtrUnsafe
      = FunPtr (VkProcType "vkCmdSetPerformanceOverrideINTEL")
-> VkProcType "vkCmdSetPerformanceOverrideINTEL"
PFN_vkCmdSetPerformanceOverrideINTEL
-> HS_vkCmdSetPerformanceOverrideINTEL
unwrapVkCmdSetPerformanceOverrideINTELUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCmdSetPerformanceOverrideINTEL")
-> VkProcType "vkCmdSetPerformanceOverrideINTEL"
unwrapVkProcPtrSafe = FunPtr (VkProcType "vkCmdSetPerformanceOverrideINTEL")
-> VkProcType "vkCmdSetPerformanceOverrideINTEL"
PFN_vkCmdSetPerformanceOverrideINTEL
-> HS_vkCmdSetPerformanceOverrideINTEL
unwrapVkCmdSetPerformanceOverrideINTELSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkAcquirePerformanceConfigurationINTEL :: CString

pattern $bVkAcquirePerformanceConfigurationINTEL :: CString
$mVkAcquirePerformanceConfigurationINTEL :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkAcquirePerformanceConfigurationINTEL <-
        (is_VkAcquirePerformanceConfigurationINTEL -> True)
  where
    VkAcquirePerformanceConfigurationINTEL
      = CString
_VkAcquirePerformanceConfigurationINTEL

{-# INLINE _VkAcquirePerformanceConfigurationINTEL #-}

_VkAcquirePerformanceConfigurationINTEL :: CString
_VkAcquirePerformanceConfigurationINTEL :: CString
_VkAcquirePerformanceConfigurationINTEL
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkAcquirePerformanceConfigurationINTEL\NUL"#

{-# INLINE is_VkAcquirePerformanceConfigurationINTEL #-}

is_VkAcquirePerformanceConfigurationINTEL :: CString -> Bool
is_VkAcquirePerformanceConfigurationINTEL :: CString -> Bool
is_VkAcquirePerformanceConfigurationINTEL
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VkAcquirePerformanceConfigurationINTEL

type VkAcquirePerformanceConfigurationINTEL =
     "vkAcquirePerformanceConfigurationINTEL"

-- | Success codes: 'VK_SUCCESS'.
--
--   Error codes: 'VK_ERROR_TOO_MANY_OBJECTS', 'VK_ERROR_OUT_OF_HOST_MEMORY'.
--
--   > VkResult vkAcquirePerformanceConfigurationINTEL
--   >     ( VkDevice device
--   >     , const VkPerformanceConfigurationAcquireInfoINTEL* pAcquireInfo
--   >     , VkPerformanceConfigurationINTEL* pConfiguration
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkAcquirePerformanceConfigurationINTEL vkAcquirePerformanceConfigurationINTEL registry at www.khronos.org>
type HS_vkAcquirePerformanceConfigurationINTEL =
     VkDevice -- ^ device
              ->
       Ptr VkPerformanceConfigurationAcquireInfoINTEL -- ^ pAcquireInfo
                                                      ->
         Ptr VkPerformanceConfigurationINTEL -- ^ pConfiguration
                                             -> IO VkResult

type PFN_vkAcquirePerformanceConfigurationINTEL =
     FunPtr HS_vkAcquirePerformanceConfigurationINTEL

foreign import ccall unsafe "dynamic"
               unwrapVkAcquirePerformanceConfigurationINTELUnsafe ::
               PFN_vkAcquirePerformanceConfigurationINTEL ->
                 HS_vkAcquirePerformanceConfigurationINTEL

foreign import ccall safe "dynamic"
               unwrapVkAcquirePerformanceConfigurationINTELSafe ::
               PFN_vkAcquirePerformanceConfigurationINTEL ->
                 HS_vkAcquirePerformanceConfigurationINTEL

instance VulkanProc "vkAcquirePerformanceConfigurationINTEL" where
    type VkProcType "vkAcquirePerformanceConfigurationINTEL" =
         HS_vkAcquirePerformanceConfigurationINTEL
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkAcquirePerformanceConfigurationINTEL

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkAcquirePerformanceConfigurationINTEL")
-> VkProcType "vkAcquirePerformanceConfigurationINTEL"
unwrapVkProcPtrUnsafe
      = FunPtr (VkProcType "vkAcquirePerformanceConfigurationINTEL")
-> VkProcType "vkAcquirePerformanceConfigurationINTEL"
PFN_vkAcquirePerformanceConfigurationINTEL
-> HS_vkAcquirePerformanceConfigurationINTEL
unwrapVkAcquirePerformanceConfigurationINTELUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkAcquirePerformanceConfigurationINTEL")
-> VkProcType "vkAcquirePerformanceConfigurationINTEL"
unwrapVkProcPtrSafe
      = FunPtr (VkProcType "vkAcquirePerformanceConfigurationINTEL")
-> VkProcType "vkAcquirePerformanceConfigurationINTEL"
PFN_vkAcquirePerformanceConfigurationINTEL
-> HS_vkAcquirePerformanceConfigurationINTEL
unwrapVkAcquirePerformanceConfigurationINTELSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkReleasePerformanceConfigurationINTEL :: CString

pattern $bVkReleasePerformanceConfigurationINTEL :: CString
$mVkReleasePerformanceConfigurationINTEL :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkReleasePerformanceConfigurationINTEL <-
        (is_VkReleasePerformanceConfigurationINTEL -> True)
  where
    VkReleasePerformanceConfigurationINTEL
      = CString
_VkReleasePerformanceConfigurationINTEL

{-# INLINE _VkReleasePerformanceConfigurationINTEL #-}

_VkReleasePerformanceConfigurationINTEL :: CString
_VkReleasePerformanceConfigurationINTEL :: CString
_VkReleasePerformanceConfigurationINTEL
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkReleasePerformanceConfigurationINTEL\NUL"#

{-# INLINE is_VkReleasePerformanceConfigurationINTEL #-}

is_VkReleasePerformanceConfigurationINTEL :: CString -> Bool
is_VkReleasePerformanceConfigurationINTEL :: CString -> Bool
is_VkReleasePerformanceConfigurationINTEL
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VkReleasePerformanceConfigurationINTEL

type VkReleasePerformanceConfigurationINTEL =
     "vkReleasePerformanceConfigurationINTEL"

-- | Success codes: 'VK_SUCCESS'.
--
--   Error codes: 'VK_ERROR_TOO_MANY_OBJECTS', 'VK_ERROR_OUT_OF_HOST_MEMORY'.
--
--   > VkResult vkReleasePerformanceConfigurationINTEL
--   >     ( VkDevice device
--   >     , VkPerformanceConfigurationINTEL configuration
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkReleasePerformanceConfigurationINTEL vkReleasePerformanceConfigurationINTEL registry at www.khronos.org>
type HS_vkReleasePerformanceConfigurationINTEL =
     VkDevice -- ^ device
              -> VkPerformanceConfigurationINTEL -- ^ configuration
                                                 -> IO VkResult

type PFN_vkReleasePerformanceConfigurationINTEL =
     FunPtr HS_vkReleasePerformanceConfigurationINTEL

foreign import ccall unsafe "dynamic"
               unwrapVkReleasePerformanceConfigurationINTELUnsafe ::
               PFN_vkReleasePerformanceConfigurationINTEL ->
                 HS_vkReleasePerformanceConfigurationINTEL

foreign import ccall safe "dynamic"
               unwrapVkReleasePerformanceConfigurationINTELSafe ::
               PFN_vkReleasePerformanceConfigurationINTEL ->
                 HS_vkReleasePerformanceConfigurationINTEL

instance VulkanProc "vkReleasePerformanceConfigurationINTEL" where
    type VkProcType "vkReleasePerformanceConfigurationINTEL" =
         HS_vkReleasePerformanceConfigurationINTEL
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkReleasePerformanceConfigurationINTEL

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkReleasePerformanceConfigurationINTEL")
-> VkProcType "vkReleasePerformanceConfigurationINTEL"
unwrapVkProcPtrUnsafe
      = FunPtr (VkProcType "vkReleasePerformanceConfigurationINTEL")
-> VkProcType "vkReleasePerformanceConfigurationINTEL"
PFN_vkReleasePerformanceConfigurationINTEL
-> HS_vkReleasePerformanceConfigurationINTEL
unwrapVkReleasePerformanceConfigurationINTELUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkReleasePerformanceConfigurationINTEL")
-> VkProcType "vkReleasePerformanceConfigurationINTEL"
unwrapVkProcPtrSafe
      = FunPtr (VkProcType "vkReleasePerformanceConfigurationINTEL")
-> VkProcType "vkReleasePerformanceConfigurationINTEL"
PFN_vkReleasePerformanceConfigurationINTEL
-> HS_vkReleasePerformanceConfigurationINTEL
unwrapVkReleasePerformanceConfigurationINTELSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkQueueSetPerformanceConfigurationINTEL :: CString

pattern $bVkQueueSetPerformanceConfigurationINTEL :: CString
$mVkQueueSetPerformanceConfigurationINTEL :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkQueueSetPerformanceConfigurationINTEL <-
        (is_VkQueueSetPerformanceConfigurationINTEL -> True)
  where
    VkQueueSetPerformanceConfigurationINTEL
      = CString
_VkQueueSetPerformanceConfigurationINTEL

{-# INLINE _VkQueueSetPerformanceConfigurationINTEL #-}

_VkQueueSetPerformanceConfigurationINTEL :: CString
_VkQueueSetPerformanceConfigurationINTEL :: CString
_VkQueueSetPerformanceConfigurationINTEL
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkQueueSetPerformanceConfigurationINTEL\NUL"#

{-# INLINE is_VkQueueSetPerformanceConfigurationINTEL #-}

is_VkQueueSetPerformanceConfigurationINTEL :: CString -> Bool
is_VkQueueSetPerformanceConfigurationINTEL :: CString -> Bool
is_VkQueueSetPerformanceConfigurationINTEL
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VkQueueSetPerformanceConfigurationINTEL

type VkQueueSetPerformanceConfigurationINTEL =
     "vkQueueSetPerformanceConfigurationINTEL"

-- | Success codes: 'VK_SUCCESS'.
--
--   Error codes: 'VK_ERROR_TOO_MANY_OBJECTS', 'VK_ERROR_OUT_OF_HOST_MEMORY'.
--
--   > VkResult vkQueueSetPerformanceConfigurationINTEL
--   >     ( VkQueue queue
--   >     , VkPerformanceConfigurationINTEL configuration
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkQueueSetPerformanceConfigurationINTEL vkQueueSetPerformanceConfigurationINTEL registry at www.khronos.org>
type HS_vkQueueSetPerformanceConfigurationINTEL =
     VkQueue -- ^ queue
             -> VkPerformanceConfigurationINTEL -- ^ configuration
                                                -> IO VkResult

type PFN_vkQueueSetPerformanceConfigurationINTEL =
     FunPtr HS_vkQueueSetPerformanceConfigurationINTEL

foreign import ccall unsafe "dynamic"
               unwrapVkQueueSetPerformanceConfigurationINTELUnsafe ::
               PFN_vkQueueSetPerformanceConfigurationINTEL ->
                 HS_vkQueueSetPerformanceConfigurationINTEL

foreign import ccall safe "dynamic"
               unwrapVkQueueSetPerformanceConfigurationINTELSafe ::
               PFN_vkQueueSetPerformanceConfigurationINTEL ->
                 HS_vkQueueSetPerformanceConfigurationINTEL

instance VulkanProc "vkQueueSetPerformanceConfigurationINTEL" where
    type VkProcType "vkQueueSetPerformanceConfigurationINTEL" =
         HS_vkQueueSetPerformanceConfigurationINTEL
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkQueueSetPerformanceConfigurationINTEL

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkQueueSetPerformanceConfigurationINTEL")
-> VkProcType "vkQueueSetPerformanceConfigurationINTEL"
unwrapVkProcPtrUnsafe
      = FunPtr (VkProcType "vkQueueSetPerformanceConfigurationINTEL")
-> VkProcType "vkQueueSetPerformanceConfigurationINTEL"
PFN_vkQueueSetPerformanceConfigurationINTEL
-> HS_vkQueueSetPerformanceConfigurationINTEL
unwrapVkQueueSetPerformanceConfigurationINTELUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkQueueSetPerformanceConfigurationINTEL")
-> VkProcType "vkQueueSetPerformanceConfigurationINTEL"
unwrapVkProcPtrSafe
      = FunPtr (VkProcType "vkQueueSetPerformanceConfigurationINTEL")
-> VkProcType "vkQueueSetPerformanceConfigurationINTEL"
PFN_vkQueueSetPerformanceConfigurationINTEL
-> HS_vkQueueSetPerformanceConfigurationINTEL
unwrapVkQueueSetPerformanceConfigurationINTELSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkGetPerformanceParameterINTEL :: CString

pattern $bVkGetPerformanceParameterINTEL :: CString
$mVkGetPerformanceParameterINTEL :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkGetPerformanceParameterINTEL <-
        (is_VkGetPerformanceParameterINTEL -> True)
  where
    VkGetPerformanceParameterINTEL = CString
_VkGetPerformanceParameterINTEL

{-# INLINE _VkGetPerformanceParameterINTEL #-}

_VkGetPerformanceParameterINTEL :: CString
_VkGetPerformanceParameterINTEL :: CString
_VkGetPerformanceParameterINTEL
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkGetPerformanceParameterINTEL\NUL"#

{-# INLINE is_VkGetPerformanceParameterINTEL #-}

is_VkGetPerformanceParameterINTEL :: CString -> Bool
is_VkGetPerformanceParameterINTEL :: CString -> Bool
is_VkGetPerformanceParameterINTEL
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VkGetPerformanceParameterINTEL

type VkGetPerformanceParameterINTEL =
     "vkGetPerformanceParameterINTEL"

-- | Success codes: 'VK_SUCCESS'.
--
--   Error codes: 'VK_ERROR_TOO_MANY_OBJECTS', 'VK_ERROR_OUT_OF_HOST_MEMORY'.
--
--   > VkResult vkGetPerformanceParameterINTEL
--   >     ( VkDevice device
--   >     , VkPerformanceParameterTypeINTEL parameter
--   >     , VkPerformanceValueINTEL* pValue
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkGetPerformanceParameterINTEL vkGetPerformanceParameterINTEL registry at www.khronos.org>
type HS_vkGetPerformanceParameterINTEL =
     VkDevice -- ^ device
              ->
       VkPerformanceParameterTypeINTEL -- ^ parameter
                                       ->
         Ptr VkPerformanceValueINTEL -- ^ pValue
                                     -> IO VkResult

type PFN_vkGetPerformanceParameterINTEL =
     FunPtr HS_vkGetPerformanceParameterINTEL

foreign import ccall unsafe "dynamic"
               unwrapVkGetPerformanceParameterINTELUnsafe ::
               PFN_vkGetPerformanceParameterINTEL ->
                 HS_vkGetPerformanceParameterINTEL

foreign import ccall safe "dynamic"
               unwrapVkGetPerformanceParameterINTELSafe ::
               PFN_vkGetPerformanceParameterINTEL ->
                 HS_vkGetPerformanceParameterINTEL

instance VulkanProc "vkGetPerformanceParameterINTEL" where
    type VkProcType "vkGetPerformanceParameterINTEL" =
         HS_vkGetPerformanceParameterINTEL
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkGetPerformanceParameterINTEL

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkGetPerformanceParameterINTEL")
-> VkProcType "vkGetPerformanceParameterINTEL"
unwrapVkProcPtrUnsafe = FunPtr (VkProcType "vkGetPerformanceParameterINTEL")
-> VkProcType "vkGetPerformanceParameterINTEL"
PFN_vkGetPerformanceParameterINTEL
-> HS_vkGetPerformanceParameterINTEL
unwrapVkGetPerformanceParameterINTELUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkGetPerformanceParameterINTEL")
-> VkProcType "vkGetPerformanceParameterINTEL"
unwrapVkProcPtrSafe = FunPtr (VkProcType "vkGetPerformanceParameterINTEL")
-> VkProcType "vkGetPerformanceParameterINTEL"
PFN_vkGetPerformanceParameterINTEL
-> HS_vkGetPerformanceParameterINTEL
unwrapVkGetPerformanceParameterINTELSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VK_INTEL_PERFORMANCE_QUERY_SPEC_VERSION :: (Num a, Eq a) =>
        a

pattern $bVK_INTEL_PERFORMANCE_QUERY_SPEC_VERSION :: forall a. (Num a, Eq a) => a
$mVK_INTEL_PERFORMANCE_QUERY_SPEC_VERSION :: forall {r} {a}.
(Num a, Eq a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
VK_INTEL_PERFORMANCE_QUERY_SPEC_VERSION = 2

type VK_INTEL_PERFORMANCE_QUERY_SPEC_VERSION = 2

pattern VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: CString

pattern $bVK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: CString
$mVK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME <-
        (is_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME -> True)
  where
    VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME
      = CString
_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME

{-# INLINE _VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME #-}

_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: CString
_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: CString
_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"VK_INTEL_performance_query\NUL"#

{-# INLINE is_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME #-}

is_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: CString -> Bool
is_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: CString -> Bool
is_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME
  = (Ordering
EQ Ordering -> Ordering -> Bool
forall a. Eq a => a -> a -> Bool
==) (Ordering -> Bool) -> (CString -> Ordering) -> CString -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CString -> CString -> Ordering
cmpCStrings CString
_VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME

type VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME =
     "VK_INTEL_performance_query"

pattern VK_STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL
        :: VkStructureType

pattern $bVK_STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL :: VkStructureType
$mVK_STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL :: forall {r}. VkStructureType -> (Void# -> r) -> (Void# -> r) -> r
VK_STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL
        = VkStructureType 1000210000

-- | Backwards-compatible alias
pattern $bVK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL :: VkStructureType
$mVK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL :: forall {r}. VkStructureType -> (Void# -> r) -> (Void# -> r) -> r
VK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL =
        VK_STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL

pattern VK_STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL ::
        VkStructureType

pattern $bVK_STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL :: VkStructureType
$mVK_STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL :: forall {r}. VkStructureType -> (Void# -> r) -> (Void# -> r) -> r
VK_STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL =
        VkStructureType 1000210001

pattern VK_STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL ::
        VkStructureType

pattern $bVK_STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL :: VkStructureType
$mVK_STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL :: forall {r}. VkStructureType -> (Void# -> r) -> (Void# -> r) -> r
VK_STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL =
        VkStructureType 1000210002

pattern VK_STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL ::
        VkStructureType

pattern $bVK_STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL :: VkStructureType
$mVK_STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL :: forall {r}. VkStructureType -> (Void# -> r) -> (Void# -> r) -> r
VK_STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL =
        VkStructureType 1000210003

pattern VK_STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL ::
        VkStructureType

pattern $bVK_STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL :: VkStructureType
$mVK_STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL :: forall {r}. VkStructureType -> (Void# -> r) -> (Void# -> r) -> r
VK_STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL =
        VkStructureType 1000210004

pattern VK_STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL
        :: VkStructureType

pattern $bVK_STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL :: VkStructureType
$mVK_STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL :: forall {r}. VkStructureType -> (Void# -> r) -> (Void# -> r) -> r
VK_STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL
        = VkStructureType 1000210005

pattern VK_QUERY_TYPE_PERFORMANCE_QUERY_INTEL :: VkQueryType

pattern $bVK_QUERY_TYPE_PERFORMANCE_QUERY_INTEL :: VkQueryType
$mVK_QUERY_TYPE_PERFORMANCE_QUERY_INTEL :: forall {r}. VkQueryType -> (Void# -> r) -> (Void# -> r) -> r
VK_QUERY_TYPE_PERFORMANCE_QUERY_INTEL =
        VkQueryType 1000210000

pattern VK_OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL ::
        VkObjectType

pattern $bVK_OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL :: VkObjectType
$mVK_OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL :: forall {r}. VkObjectType -> (Void# -> r) -> (Void# -> r) -> r
VK_OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL =
        VkObjectType 1000210000