{-# OPTIONS_GHC -fno-warn-missing-pattern-synonym-signatures#-}
{-# OPTIONS_GHC -fno-warn-orphans#-}
{-# OPTIONS_GHC -fno-warn-unused-imports#-}
{-# 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_EXT_debug_report
       (-- * Vulkan extension: @VK_EXT_debug_report@
        -- |
        --
        -- supported: @vulkan@
        --
        -- contact: @Courtney Goeltzenleuchter @courtney-g@
        --
        -- author: @GOOGLE@
        --
        -- type: @instance@
        --
        -- Extension number: @12@
        module Graphics.Vulkan.Marshal, VkApplicationInfo,
        AHardwareBuffer(), ANativeWindow(), CAMetalLayer(), VkBool32(..),
        VkDeviceAddress(..), VkDeviceSize(..), VkFlags(..),
        VkSampleMask(..), VkDebugReportCallbackCreateInfoEXT,
        VkDebugReportBitmaskEXT(..), VkDebugReportObjectTypeEXT(..),
        pattern VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_EXT,
        pattern VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT,
        VkDebugUtilsMessageSeverityBitmaskEXT(..),
        VkDebugUtilsMessageTypeBitmaskEXT(..), VkDebugReportFlagBitsEXT(),
        VkDebugReportFlagsEXT(), VkDebugUtilsMessageSeverityFlagBitsEXT(),
        VkDebugUtilsMessageSeverityFlagsEXT(),
        VkDebugUtilsMessageTypeFlagBitsEXT(),
        VkDebugUtilsMessageTypeFlagsEXT(),
        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(..), VkInstanceCreateInfo,
        VkStructureType(..), -- > #include "vk_platform.h"
                             VkCreateDebugReportCallbackEXT,
        pattern VkCreateDebugReportCallbackEXT,
        HS_vkCreateDebugReportCallbackEXT,
        PFN_vkCreateDebugReportCallbackEXT,
        VkDestroyDebugReportCallbackEXT,
        pattern VkDestroyDebugReportCallbackEXT,
        HS_vkDestroyDebugReportCallbackEXT,
        PFN_vkDestroyDebugReportCallbackEXT, VkDebugReportMessageEXT,
        pattern VkDebugReportMessageEXT, HS_vkDebugReportMessageEXT,
        PFN_vkDebugReportMessageEXT, VkInternalAllocationType(..),
        VkResult(..), VkSystemAllocationScope(..), newVkAllocationFunction,
        newVkDebugReportCallbackEXT, newVkDebugUtilsMessengerCallbackEXT,
        newVkFreeFunction, newVkInternalAllocationNotification,
        newVkInternalFreeNotification, newVkReallocationFunction,
        newVkVoidFunction, unwrapVkAllocationFunction,
        unwrapVkDebugReportCallbackEXT,
        unwrapVkDebugUtilsMessengerCallbackEXT, unwrapVkFreeFunction,
        unwrapVkInternalAllocationNotification,
        unwrapVkInternalFreeNotification, unwrapVkReallocationFunction,
        unwrapVkVoidFunction, HS_vkAllocationFunction,
        HS_vkDebugReportCallbackEXT, HS_vkDebugUtilsMessengerCallbackEXT,
        HS_vkFreeFunction, HS_vkInternalAllocationNotification,
        HS_vkInternalFreeNotification, HS_vkReallocationFunction,
        HS_vkVoidFunction, PFN_vkAllocationFunction,
        PFN_vkDebugReportCallbackEXT, PFN_vkDebugUtilsMessengerCallbackEXT,
        PFN_vkFreeFunction, PFN_vkInternalAllocationNotification,
        PFN_vkInternalFreeNotification, PFN_vkReallocationFunction,
        PFN_vkVoidFunction, 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(),
        VkAllocationCallbacks, VkDebugMarkerMarkerInfoEXT,
        VkDebugMarkerObjectNameInfoEXT, VkDebugMarkerObjectTagInfoEXT,
        VkDebugUtilsObjectTagInfoEXT, VK_EXT_DEBUG_REPORT_SPEC_VERSION,
        pattern VK_EXT_DEBUG_REPORT_SPEC_VERSION,
        VK_EXT_DEBUG_REPORT_EXTENSION_NAME,
        pattern VK_EXT_DEBUG_REPORT_EXTENSION_NAME,
        pattern VK_STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT,
        pattern VK_STRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT,
        pattern VK_ERROR_VALIDATION_FAILED_EXT,
        pattern VK_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT,
        pattern VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT,
        pattern VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT)
       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.Debug
import Graphics.Vulkan.Types.Enum.InternalAllocationType
import Graphics.Vulkan.Types.Enum.ObjectType             (VkObjectType (..))
import Graphics.Vulkan.Types.Enum.Result
import Graphics.Vulkan.Types.Enum.StructureType
import Graphics.Vulkan.Types.Enum.SystemAllocationScope
import Graphics.Vulkan.Types.Funcpointers
import Graphics.Vulkan.Types.Handles
import Graphics.Vulkan.Types.Struct.AllocationCallbacks
import Graphics.Vulkan.Types.Struct.ApplicationInfo
import Graphics.Vulkan.Types.Struct.Debug
import Graphics.Vulkan.Types.Struct.InstanceCreateInfo

pattern VkCreateDebugReportCallbackEXT :: CString

pattern $bVkCreateDebugReportCallbackEXT :: CString
$mVkCreateDebugReportCallbackEXT :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkCreateDebugReportCallbackEXT <-
        (is_VkCreateDebugReportCallbackEXT -> True)
  where
    VkCreateDebugReportCallbackEXT = CString
_VkCreateDebugReportCallbackEXT

{-# INLINE _VkCreateDebugReportCallbackEXT #-}

_VkCreateDebugReportCallbackEXT :: CString
_VkCreateDebugReportCallbackEXT :: CString
_VkCreateDebugReportCallbackEXT
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkCreateDebugReportCallbackEXT\NUL"#

{-# INLINE is_VkCreateDebugReportCallbackEXT #-}

is_VkCreateDebugReportCallbackEXT :: CString -> Bool
is_VkCreateDebugReportCallbackEXT :: CString -> Bool
is_VkCreateDebugReportCallbackEXT
  = (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
_VkCreateDebugReportCallbackEXT

type VkCreateDebugReportCallbackEXT =
     "vkCreateDebugReportCallbackEXT"

-- | Success codes: 'VK_SUCCESS'.
--
--   Error codes: 'VK_ERROR_OUT_OF_HOST_MEMORY'.
--
--   > VkResult vkCreateDebugReportCallbackEXT
--   >     ( VkInstance instance
--   >     , const VkDebugReportCallbackCreateInfoEXT* pCreateInfo
--   >     , const VkAllocationCallbacks* pAllocator
--   >     , VkDebugReportCallbackEXT* pCallback
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCreateDebugReportCallbackEXT vkCreateDebugReportCallbackEXT registry at www.khronos.org>
type HS_vkCreateDebugReportCallbackEXT =
     VkInstance -- ^ instance
                ->
       Ptr VkDebugReportCallbackCreateInfoEXT -- ^ pCreateInfo
                                              ->
         Ptr VkAllocationCallbacks -- ^ pAllocator
                                   ->
           Ptr VkDebugReportCallbackEXT -- ^ pCallback
                                        -> IO VkResult

type PFN_vkCreateDebugReportCallbackEXT =
     FunPtr HS_vkCreateDebugReportCallbackEXT

foreign import ccall unsafe "dynamic"
               unwrapVkCreateDebugReportCallbackEXTUnsafe ::
               PFN_vkCreateDebugReportCallbackEXT ->
                 HS_vkCreateDebugReportCallbackEXT

foreign import ccall safe "dynamic"
               unwrapVkCreateDebugReportCallbackEXTSafe ::
               PFN_vkCreateDebugReportCallbackEXT ->
                 HS_vkCreateDebugReportCallbackEXT

instance VulkanProc "vkCreateDebugReportCallbackEXT" where
    type VkProcType "vkCreateDebugReportCallbackEXT" =
         HS_vkCreateDebugReportCallbackEXT
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkCreateDebugReportCallbackEXT

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkCreateDebugReportCallbackEXT")
-> VkProcType "vkCreateDebugReportCallbackEXT"
unwrapVkProcPtrUnsafe = FunPtr (VkProcType "vkCreateDebugReportCallbackEXT")
-> VkProcType "vkCreateDebugReportCallbackEXT"
PFN_vkCreateDebugReportCallbackEXT
-> HS_vkCreateDebugReportCallbackEXT
unwrapVkCreateDebugReportCallbackEXTUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkCreateDebugReportCallbackEXT")
-> VkProcType "vkCreateDebugReportCallbackEXT"
unwrapVkProcPtrSafe = FunPtr (VkProcType "vkCreateDebugReportCallbackEXT")
-> VkProcType "vkCreateDebugReportCallbackEXT"
PFN_vkCreateDebugReportCallbackEXT
-> HS_vkCreateDebugReportCallbackEXT
unwrapVkCreateDebugReportCallbackEXTSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkDestroyDebugReportCallbackEXT :: CString

pattern $bVkDestroyDebugReportCallbackEXT :: CString
$mVkDestroyDebugReportCallbackEXT :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkDestroyDebugReportCallbackEXT <-
        (is_VkDestroyDebugReportCallbackEXT -> True)
  where
    VkDestroyDebugReportCallbackEXT = CString
_VkDestroyDebugReportCallbackEXT

{-# INLINE _VkDestroyDebugReportCallbackEXT #-}

_VkDestroyDebugReportCallbackEXT :: CString
_VkDestroyDebugReportCallbackEXT :: CString
_VkDestroyDebugReportCallbackEXT
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkDestroyDebugReportCallbackEXT\NUL"#

{-# INLINE is_VkDestroyDebugReportCallbackEXT #-}

is_VkDestroyDebugReportCallbackEXT :: CString -> Bool
is_VkDestroyDebugReportCallbackEXT :: CString -> Bool
is_VkDestroyDebugReportCallbackEXT
  = (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
_VkDestroyDebugReportCallbackEXT

type VkDestroyDebugReportCallbackEXT =
     "vkDestroyDebugReportCallbackEXT"

-- | > void vkDestroyDebugReportCallbackEXT
--   >     ( VkInstance instance
--   >     , VkDebugReportCallbackEXT callback
--   >     , const VkAllocationCallbacks* pAllocator
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkDestroyDebugReportCallbackEXT vkDestroyDebugReportCallbackEXT registry at www.khronos.org>
type HS_vkDestroyDebugReportCallbackEXT =
     VkInstance -- ^ instance
                ->
       VkDebugReportCallbackEXT -- ^ callback
                                -> Ptr VkAllocationCallbacks -- ^ pAllocator
                                                             -> IO ()

type PFN_vkDestroyDebugReportCallbackEXT =
     FunPtr HS_vkDestroyDebugReportCallbackEXT

foreign import ccall unsafe "dynamic"
               unwrapVkDestroyDebugReportCallbackEXTUnsafe ::
               PFN_vkDestroyDebugReportCallbackEXT ->
                 HS_vkDestroyDebugReportCallbackEXT

foreign import ccall safe "dynamic"
               unwrapVkDestroyDebugReportCallbackEXTSafe ::
               PFN_vkDestroyDebugReportCallbackEXT ->
                 HS_vkDestroyDebugReportCallbackEXT

instance VulkanProc "vkDestroyDebugReportCallbackEXT" where
    type VkProcType "vkDestroyDebugReportCallbackEXT" =
         HS_vkDestroyDebugReportCallbackEXT
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkDestroyDebugReportCallbackEXT

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkDestroyDebugReportCallbackEXT")
-> VkProcType "vkDestroyDebugReportCallbackEXT"
unwrapVkProcPtrUnsafe = FunPtr (VkProcType "vkDestroyDebugReportCallbackEXT")
-> VkProcType "vkDestroyDebugReportCallbackEXT"
PFN_vkDestroyDebugReportCallbackEXT
-> HS_vkDestroyDebugReportCallbackEXT
unwrapVkDestroyDebugReportCallbackEXTUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkDestroyDebugReportCallbackEXT")
-> VkProcType "vkDestroyDebugReportCallbackEXT"
unwrapVkProcPtrSafe = FunPtr (VkProcType "vkDestroyDebugReportCallbackEXT")
-> VkProcType "vkDestroyDebugReportCallbackEXT"
PFN_vkDestroyDebugReportCallbackEXT
-> HS_vkDestroyDebugReportCallbackEXT
unwrapVkDestroyDebugReportCallbackEXTSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

pattern VkDebugReportMessageEXT :: CString

pattern $bVkDebugReportMessageEXT :: CString
$mVkDebugReportMessageEXT :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VkDebugReportMessageEXT <-
        (is_VkDebugReportMessageEXT -> True)
  where
    VkDebugReportMessageEXT = CString
_VkDebugReportMessageEXT

{-# INLINE _VkDebugReportMessageEXT #-}

_VkDebugReportMessageEXT :: CString
_VkDebugReportMessageEXT :: CString
_VkDebugReportMessageEXT = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"vkDebugReportMessageEXT\NUL"#

{-# INLINE is_VkDebugReportMessageEXT #-}

is_VkDebugReportMessageEXT :: CString -> Bool
is_VkDebugReportMessageEXT :: CString -> Bool
is_VkDebugReportMessageEXT
  = (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
_VkDebugReportMessageEXT

type VkDebugReportMessageEXT = "vkDebugReportMessageEXT"

-- | > void vkDebugReportMessageEXT
--   >     ( VkInstance instance
--   >     , VkDebugReportFlagsEXT flags
--   >     , VkDebugReportObjectTypeEXT objectType
--   >     , uint64_t object
--   >     , size_t location
--   >     , int32_t messageCode
--   >     , const char* pLayerPrefix
--   >     , const char* pMessage
--   >     )
--
--   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkDebugReportMessageEXT vkDebugReportMessageEXT registry at www.khronos.org>
type HS_vkDebugReportMessageEXT =
     VkInstance -- ^ instance
                ->
       VkDebugReportFlagsEXT -- ^ flags
                             ->
         VkDebugReportObjectTypeEXT -- ^ objectType
                                    ->
           Word64 -- ^ object
                  -> CSize -- ^ location
                           -> Int32 -- ^ messageCode
                                    -> CString -- ^ pLayerPrefix
                                               -> CString -- ^ pMessage
                                                          -> IO ()

type PFN_vkDebugReportMessageEXT =
     FunPtr HS_vkDebugReportMessageEXT

foreign import ccall unsafe "dynamic"
               unwrapVkDebugReportMessageEXTUnsafe ::
               PFN_vkDebugReportMessageEXT -> HS_vkDebugReportMessageEXT

foreign import ccall safe "dynamic"
               unwrapVkDebugReportMessageEXTSafe ::
               PFN_vkDebugReportMessageEXT -> HS_vkDebugReportMessageEXT

instance VulkanProc "vkDebugReportMessageEXT" where
    type VkProcType "vkDebugReportMessageEXT" =
         HS_vkDebugReportMessageEXT
    vkProcSymbol :: CString
vkProcSymbol = CString
_VkDebugReportMessageEXT

    {-# INLINE vkProcSymbol #-}
    unwrapVkProcPtrUnsafe :: FunPtr (VkProcType "vkDebugReportMessageEXT")
-> VkProcType "vkDebugReportMessageEXT"
unwrapVkProcPtrUnsafe = FunPtr (VkProcType "vkDebugReportMessageEXT")
-> VkProcType "vkDebugReportMessageEXT"
PFN_vkDebugReportMessageEXT -> HS_vkDebugReportMessageEXT
unwrapVkDebugReportMessageEXTUnsafe

    {-# INLINE unwrapVkProcPtrUnsafe #-}
    unwrapVkProcPtrSafe :: FunPtr (VkProcType "vkDebugReportMessageEXT")
-> VkProcType "vkDebugReportMessageEXT"
unwrapVkProcPtrSafe = FunPtr (VkProcType "vkDebugReportMessageEXT")
-> VkProcType "vkDebugReportMessageEXT"
PFN_vkDebugReportMessageEXT -> HS_vkDebugReportMessageEXT
unwrapVkDebugReportMessageEXTSafe

    {-# INLINE unwrapVkProcPtrSafe #-}

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

pattern $bVK_EXT_DEBUG_REPORT_SPEC_VERSION :: forall a. (Num a, Eq a) => a
$mVK_EXT_DEBUG_REPORT_SPEC_VERSION :: forall {r} {a}.
(Num a, Eq a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
VK_EXT_DEBUG_REPORT_SPEC_VERSION = 9

type VK_EXT_DEBUG_REPORT_SPEC_VERSION = 9

pattern VK_EXT_DEBUG_REPORT_EXTENSION_NAME :: CString

pattern $bVK_EXT_DEBUG_REPORT_EXTENSION_NAME :: CString
$mVK_EXT_DEBUG_REPORT_EXTENSION_NAME :: forall {r}. CString -> (Void# -> r) -> (Void# -> r) -> r
VK_EXT_DEBUG_REPORT_EXTENSION_NAME <-
        (is_VK_EXT_DEBUG_REPORT_EXTENSION_NAME -> True)
  where
    VK_EXT_DEBUG_REPORT_EXTENSION_NAME
      = CString
_VK_EXT_DEBUG_REPORT_EXTENSION_NAME

{-# INLINE _VK_EXT_DEBUG_REPORT_EXTENSION_NAME #-}

_VK_EXT_DEBUG_REPORT_EXTENSION_NAME :: CString
_VK_EXT_DEBUG_REPORT_EXTENSION_NAME :: CString
_VK_EXT_DEBUG_REPORT_EXTENSION_NAME
  = Addr# -> CString
forall a. Addr# -> Ptr a
Ptr Addr#
"VK_EXT_debug_report\NUL"#

{-# INLINE is_VK_EXT_DEBUG_REPORT_EXTENSION_NAME #-}

is_VK_EXT_DEBUG_REPORT_EXTENSION_NAME :: CString -> Bool
is_VK_EXT_DEBUG_REPORT_EXTENSION_NAME :: CString -> Bool
is_VK_EXT_DEBUG_REPORT_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_EXT_DEBUG_REPORT_EXTENSION_NAME

type VK_EXT_DEBUG_REPORT_EXTENSION_NAME = "VK_EXT_debug_report"

pattern VK_STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT ::
        VkStructureType

pattern $bVK_STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT :: VkStructureType
$mVK_STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT :: forall {r}. VkStructureType -> (Void# -> r) -> (Void# -> r) -> r
VK_STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT =
        VkStructureType 1000011000

-- | Backwards-compatible alias containing a typo
pattern $bVK_STRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT :: VkStructureType
$mVK_STRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT :: forall {r}. VkStructureType -> (Void# -> r) -> (Void# -> r) -> r
VK_STRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT =
        VK_STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT

pattern VK_ERROR_VALIDATION_FAILED_EXT :: VkResult

pattern $bVK_ERROR_VALIDATION_FAILED_EXT :: VkResult
$mVK_ERROR_VALIDATION_FAILED_EXT :: forall {r}. VkResult -> (Void# -> r) -> (Void# -> r) -> r
VK_ERROR_VALIDATION_FAILED_EXT = VkResult (-1000011001)

-- | VkDebugReportCallbackEXT
pattern VK_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT :: VkObjectType

pattern $bVK_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT :: VkObjectType
$mVK_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT :: forall {r}. VkObjectType -> (Void# -> r) -> (Void# -> r) -> r
VK_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT =
        VkObjectType 1000011000

pattern VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT ::
        VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT :: forall {r}.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT =
        VkDebugReportObjectTypeEXT 1000156000

pattern VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT
        :: VkDebugReportObjectTypeEXT

pattern $bVK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT :: VkDebugReportObjectTypeEXT
$mVK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT :: forall {r}.
VkDebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT
        = VkDebugReportObjectTypeEXT 1000085000