{-# language CPP #-}
-- | = Name
--
-- VK_EXT_debug_report - instance extension
--
-- == VK_EXT_debug_report
--
-- [__Name String__]
--     @VK_EXT_debug_report@
--
-- [__Extension Type__]
--     Instance extension
--
-- [__Registered Extension Number__]
--     12
--
-- [__Revision__]
--     10
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
-- [__Deprecation state__]
--
--     -   /Deprecated/ by @VK_EXT_debug_utils@ extension
--
-- [__Special Use__]
--
--     -   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-compatibility-specialuse Debugging tools>
--
-- [__Contact__]
--
--     -   Courtney Goeltzenleuchter
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_debug_report] @courtney-g%0A<<Here describe the issue or question you have about the VK_EXT_debug_report extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2020-12-14
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Courtney Goeltzenleuchter, LunarG
--
--     -   Dan Ginsburg, Valve
--
--     -   Jon Ashburn, LunarG
--
--     -   Mark Lobodzinski, LunarG
--
-- == Description
--
-- Due to the nature of the Vulkan interface, there is very little error
-- information available to the developer and application. By enabling
-- optional validation layers and using the @VK_EXT_debug_report@
-- extension, developers /can/ obtain much more detailed feedback on the
-- application’s use of Vulkan. This extension defines a way for layers and
-- the implementation to call back to the application for events of
-- interest to the application.
--
-- == New Object Types
--
-- -   'Vulkan.Extensions.Handles.DebugReportCallbackEXT'
--
-- == New Commands
--
-- -   'createDebugReportCallbackEXT'
--
-- -   'debugReportMessageEXT'
--
-- -   'destroyDebugReportCallbackEXT'
--
-- == New Structures
--
-- -   Extending 'Vulkan.Core10.DeviceInitialization.InstanceCreateInfo':
--
--     -   'DebugReportCallbackCreateInfoEXT'
--
-- == New Function Pointers
--
-- -   'PFN_vkDebugReportCallbackEXT'
--
-- == New Enums
--
-- -   'DebugReportFlagBitsEXT'
--
-- -   'DebugReportObjectTypeEXT'
--
-- == New Bitmasks
--
-- -   'DebugReportFlagsEXT'
--
-- == New Enum Constants
--
-- -   'EXT_DEBUG_REPORT_EXTENSION_NAME'
--
-- -   'EXT_DEBUG_REPORT_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.ObjectType.ObjectType':
--
--     -   'Vulkan.Core10.Enums.ObjectType.OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.Result.Result':
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_VALIDATION_FAILED_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT'
--
--     -   'STRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT'
--
-- If
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#versions-1.1 Version 1.1>
-- is supported:
--
-- -   Extending 'DebugReportObjectTypeEXT':
--
--     -   'DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT'
--
--     -   'DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT'
--
-- == Examples
--
-- @VK_EXT_debug_report@ allows an application to register multiple
-- callbacks with the validation layers. Some callbacks may log the
-- information to a file, others may cause a debug break point or other
-- application defined behavior. An application /can/ register callbacks
-- even when no validation layers are enabled, but they will only be called
-- for loader and, if implemented, driver events.
--
-- To capture events that occur while creating or destroying an instance an
-- application /can/ link a 'DebugReportCallbackCreateInfoEXT' structure to
-- the @pNext@ element of the
-- 'Vulkan.Core10.DeviceInitialization.InstanceCreateInfo' structure given
-- to 'Vulkan.Core10.DeviceInitialization.createInstance'.
--
-- Example uses: Create three callback objects. One will log errors and
-- warnings to the debug console using Windows @OutputDebugString@. The
-- second will cause the debugger to break at that callback when an error
-- happens and the third will log warnings to stdout.
--
-- >     VkResult res;
-- >     VkDebugReportCallbackEXT cb1, cb2, cb3;
-- >
-- >     VkDebugReportCallbackCreateInfoEXT callback1 = {
-- >             VK_STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT,    // sType
-- >             NULL,                                                       // pNext
-- >             VK_DEBUG_REPORT_ERROR_BIT_EXT |                             // flags
-- >             VK_DEBUG_REPORT_WARNING_BIT_EXT,
-- >             myOutputDebugString,                                        // pfnCallback
-- >             NULL                                                        // pUserData
-- >     };
-- >     res = vkCreateDebugReportCallbackEXT(instance, &callback1, &cb1);
-- >     if (res != VK_SUCCESS)
-- >        /* Do error handling for VK_ERROR_OUT_OF_MEMORY */
-- >
-- >     callback.flags = VK_DEBUG_REPORT_ERROR_BIT_EXT;
-- >     callback.pfnCallback = myDebugBreak;
-- >     callback.pUserData = NULL;
-- >     res = vkCreateDebugReportCallbackEXT(instance, &callback, &cb2);
-- >     if (res != VK_SUCCESS)
-- >        /* Do error handling for VK_ERROR_OUT_OF_MEMORY */
-- >
-- >     VkDebugReportCallbackCreateInfoEXT callback3 = {
-- >             VK_STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT,    // sType
-- >             NULL,                                                       // pNext
-- >             VK_DEBUG_REPORT_WARNING_BIT_EXT,                            // flags
-- >             mystdOutLogger,                                             // pfnCallback
-- >             NULL                                                        // pUserData
-- >     };
-- >     res = vkCreateDebugReportCallbackEXT(instance, &callback3, &cb3);
-- >     if (res != VK_SUCCESS)
-- >        /* Do error handling for VK_ERROR_OUT_OF_MEMORY */
-- >
-- >     ...
-- >
-- >     /* remove callbacks when cleaning up */
-- >     vkDestroyDebugReportCallbackEXT(instance, cb1);
-- >     vkDestroyDebugReportCallbackEXT(instance, cb2);
-- >     vkDestroyDebugReportCallbackEXT(instance, cb3);
--
-- Note
--
-- In the initial release of the @VK_EXT_debug_report@ extension, the token
-- 'STRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT' was used. Starting in
-- version 2 of the extension branch,
-- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT'
-- is used instead for consistency with Vulkan naming rules. The older enum
-- is still available for backwards compatibility.
--
-- Note
--
-- In the initial release of the @VK_EXT_debug_report@ extension, the token
-- 'DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_EXT' was used. Starting in
-- version 8 of the extension branch,
-- 'DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT' is used instead
-- for consistency with Vulkan naming rules. The older enum is still
-- available for backwards compatibility.
--
-- == Issues
--
-- 1) What is the hierarchy \/ seriousness of the message flags? E.g.
-- @ERROR@ > @WARN@ > @PERF_WARN@ …​
--
-- __RESOLVED__: There is no specific hierarchy. Each bit is independent
-- and should be checked via bitwise AND. For example:
--
-- >     if (localFlags & VK_DEBUG_REPORT_ERROR_BIT_EXT) {
-- >         process error message
-- >     }
-- >     if (localFlags & VK_DEBUG_REPORT_DEBUG_BIT_EXT) {
-- >         process debug message
-- >     }
--
-- The validation layers do use them in a hierarchical way (@ERROR@ >
-- @WARN@ > @PERF@, @WARN@ > @DEBUG@ > @INFO@) and they (at least at the
-- time of this writing) only set one bit at a time. But it is not a
-- requirement of this extension.
--
-- It is possible that a layer may intercept and change, or augment the
-- flags with extension values the application’s debug report handler may
-- not be familiar with, so it is important to treat each flag
-- independently.
--
-- 2) Should there be a VU requiring
-- 'DebugReportCallbackCreateInfoEXT'::@flags@ to be non-zero?
--
-- __RESOLVED__: It may not be very useful, but we do not need VU statement
-- requiring the 'DebugReportCallbackCreateInfoEXT'::@msgFlags@ at
-- create-time to be non-zero. One can imagine that apps may prefer it as
-- it allows them to set the mask as desired - including nothing - at
-- runtime without having to check.
--
-- 3) What is the difference between 'DEBUG_REPORT_DEBUG_BIT_EXT' and
-- 'DEBUG_REPORT_INFORMATION_BIT_EXT'?
--
-- __RESOLVED__: 'DEBUG_REPORT_DEBUG_BIT_EXT' specifies information that
-- could be useful debugging the Vulkan implementation itself.
--
-- 4) How do you compare handles returned by the debug_report callback to
-- the application’s handles?
--
-- __RESOLVED__: Due to the different nature of dispatchable and
-- nondispatchable handles there is no generic way (that we know of) that
-- works for common compilers with 32bit, 64bit, C and C++. We recommend
-- applications use the same cast that the validation layers use:
--
-- +
--
-- > reinterpret_cast<uint64_t &>(dispatchableHandle)
-- > (uint64_t)(nondispatchableHandle)
--
-- + This does require that the app treat dispatchable and nondispatchable
-- handles differently.
--
-- == Version History
--
-- -   Revision 1, 2015-05-20 (Courtney Goetzenleuchter)
--
--     -   Initial draft, based on LunarG KHR spec, other KHR specs
--
-- -   Revision 2, 2016-02-16 (Courtney Goetzenleuchter)
--
--     -   Update usage, documentation
--
-- -   Revision 3, 2016-06-14 (Courtney Goetzenleuchter)
--
--     -   Update VK_EXT_DEBUG_REPORT_SPEC_VERSION to indicate added
--         support for vkCreateInstance and vkDestroyInstance
--
-- -   Revision 4, 2016-12-08 (Mark Lobodzinski)
--
--     -   Added Display_KHR, DisplayModeKHR extension objects
--
--     -   Added ObjectTable_NVX, IndirectCommandsLayout_NVX extension
--         objects
--
--     -   Bumped spec revision
--
--     -   Retroactively added version history
--
-- -   Revision 5, 2017-01-31 (Baldur Karlsson)
--
--     -   Moved definition of 'DebugReportObjectTypeEXT' from debug marker
--         chapter
--
-- -   Revision 6, 2017-01-31 (Baldur Karlsson)
--
--     -   Added
--         VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_KHR_EXT
--
-- -   Revision 7, 2017-04-20 (Courtney Goeltzenleuchter)
--
--     -   Clarify wording and address questions from developers.
--
-- -   Revision 8, 2017-04-21 (Courtney Goeltzenleuchter)
--
--     -   Remove unused enum VkDebugReportErrorEXT
--
-- -   Revision 9, 2017-09-12 (Tobias Hector)
--
--     -   Added interactions with Vulkan 1.1
--
-- -   Revision 10, 2020-12-14 (Courtney Goetzenleuchter)
--
--     -   Add issue 4 discussing matching handles returned by the
--         extension, based on suggestion in public issue 368.
--
-- == See Also
--
-- 'PFN_vkDebugReportCallbackEXT', 'DebugReportCallbackCreateInfoEXT',
-- 'Vulkan.Extensions.Handles.DebugReportCallbackEXT',
-- 'DebugReportFlagBitsEXT', 'DebugReportFlagsEXT',
-- 'DebugReportObjectTypeEXT', 'createDebugReportCallbackEXT',
-- 'debugReportMessageEXT', 'destroyDebugReportCallbackEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_report Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_debug_report  ( createDebugReportCallbackEXT
                                              , withDebugReportCallbackEXT
                                              , destroyDebugReportCallbackEXT
                                              , debugReportMessageEXT
                                              , pattern STRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT
                                              , pattern DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_EXT
                                              , pattern DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT
                                              , DebugReportCallbackCreateInfoEXT(..)
                                              , DebugReportFlagsEXT
                                              , DebugReportFlagBitsEXT( DEBUG_REPORT_INFORMATION_BIT_EXT
                                                                      , DEBUG_REPORT_WARNING_BIT_EXT
                                                                      , DEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT
                                                                      , DEBUG_REPORT_ERROR_BIT_EXT
                                                                      , DEBUG_REPORT_DEBUG_BIT_EXT
                                                                      , ..
                                                                      )
                                              , DebugReportObjectTypeEXT( DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_NV_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_CU_FUNCTION_NVX_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_CU_MODULE_NVX_EXT
                                                                        , DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT
                                                                        , ..
                                                                        )
                                              , PFN_vkDebugReportCallbackEXT
                                              , FN_vkDebugReportCallbackEXT
                                              , EXT_DEBUG_REPORT_SPEC_VERSION
                                              , pattern EXT_DEBUG_REPORT_SPEC_VERSION
                                              , EXT_DEBUG_REPORT_EXTENSION_NAME
                                              , pattern EXT_DEBUG_REPORT_EXTENSION_NAME
                                              , DebugReportCallbackEXT(..)
                                              ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Numeric (showHex)
import Data.ByteString (useAsCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Foreign.C.Types (CChar(..))
import Foreign.C.Types (CSize(..))
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.Bits (Bits)
import Data.Bits (FiniteBits)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CSize)
import Foreign.C.Types (CSize(CSize))
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 (Word64)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Extensions.Handles (DebugReportCallbackEXT)
import Vulkan.Extensions.Handles (DebugReportCallbackEXT(..))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Handles (Instance)
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Core10.Handles (Instance(Instance))
import Vulkan.Dynamic (InstanceCmds(pVkCreateDebugReportCallbackEXT))
import Vulkan.Dynamic (InstanceCmds(pVkDebugReportMessageEXT))
import Vulkan.Dynamic (InstanceCmds(pVkDestroyDebugReportCallbackEXT))
import Vulkan.Core10.Handles (Instance_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_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.Handles (DebugReportCallbackEXT(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateDebugReportCallbackEXT
  :: FunPtr (Ptr Instance_T -> Ptr DebugReportCallbackCreateInfoEXT -> Ptr AllocationCallbacks -> Ptr DebugReportCallbackEXT -> IO Result) -> Ptr Instance_T -> Ptr DebugReportCallbackCreateInfoEXT -> Ptr AllocationCallbacks -> Ptr DebugReportCallbackEXT -> IO Result

-- | vkCreateDebugReportCallbackEXT - Create a debug report callback object
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCreateDebugReportCallbackEXT-instance-parameter# @instance@
--     /must/ be a valid 'Vulkan.Core10.Handles.Instance' handle
--
-- -   #VUID-vkCreateDebugReportCallbackEXT-pCreateInfo-parameter#
--     @pCreateInfo@ /must/ be a valid pointer to a valid
--     'DebugReportCallbackCreateInfoEXT' structure
--
-- -   #VUID-vkCreateDebugReportCallbackEXT-pAllocator-parameter# If
--     @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid pointer
--     to a valid 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks'
--     structure
--
-- -   #VUID-vkCreateDebugReportCallbackEXT-pCallback-parameter#
--     @pCallback@ /must/ be a valid pointer to a
--     'Vulkan.Extensions.Handles.DebugReportCallbackEXT' handle
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_report VK_EXT_debug_report>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'DebugReportCallbackCreateInfoEXT',
-- 'Vulkan.Extensions.Handles.DebugReportCallbackEXT',
-- 'Vulkan.Core10.Handles.Instance'
createDebugReportCallbackEXT :: forall io
                              . (MonadIO io)
                             => -- | @instance@ is the instance the callback will be logged on.
                                Instance
                             -> -- | @pCreateInfo@ is a pointer to a 'DebugReportCallbackCreateInfoEXT'
                                -- structure defining the conditions under which this callback will be
                                -- called.
                                DebugReportCallbackCreateInfoEXT
                             -> -- | @pAllocator@ controls host memory allocation as described in the
                                -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                                -- chapter.
                                ("allocator" ::: Maybe AllocationCallbacks)
                             -> io (DebugReportCallbackEXT)
createDebugReportCallbackEXT :: Instance
-> DebugReportCallbackCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io DebugReportCallbackEXT
createDebugReportCallbackEXT Instance
instance' DebugReportCallbackCreateInfoEXT
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = IO DebugReportCallbackEXT -> io DebugReportCallbackEXT
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DebugReportCallbackEXT -> io DebugReportCallbackEXT)
-> (ContT DebugReportCallbackEXT IO DebugReportCallbackEXT
    -> IO DebugReportCallbackEXT)
-> ContT DebugReportCallbackEXT IO DebugReportCallbackEXT
-> io DebugReportCallbackEXT
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT DebugReportCallbackEXT IO DebugReportCallbackEXT
-> IO DebugReportCallbackEXT
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT DebugReportCallbackEXT IO DebugReportCallbackEXT
 -> io DebugReportCallbackEXT)
-> ContT DebugReportCallbackEXT IO DebugReportCallbackEXT
-> io DebugReportCallbackEXT
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateDebugReportCallbackEXTPtr :: FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pCallback" ::: Ptr DebugReportCallbackEXT)
   -> IO Result)
vkCreateDebugReportCallbackEXTPtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pCallback" ::: Ptr DebugReportCallbackEXT)
      -> IO Result)
pVkCreateDebugReportCallbackEXT (case Instance
instance' of Instance{InstanceCmds
$sel:instanceCmds:Instance :: Instance -> InstanceCmds
instanceCmds :: InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  IO () -> ContT DebugReportCallbackEXT IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DebugReportCallbackEXT IO ())
-> IO () -> ContT DebugReportCallbackEXT IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pCallback" ::: Ptr DebugReportCallbackEXT)
   -> IO Result)
vkCreateDebugReportCallbackEXTPtr FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pCallback" ::: Ptr DebugReportCallbackEXT)
   -> IO Result)
-> FunPtr
     (Ptr Instance_T
      -> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pCallback" ::: Ptr DebugReportCallbackEXT)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pCallback" ::: Ptr DebugReportCallbackEXT)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCreateDebugReportCallbackEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateDebugReportCallbackEXT' :: Ptr Instance_T
-> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pCallback" ::: Ptr DebugReportCallbackEXT)
-> IO Result
vkCreateDebugReportCallbackEXT' = FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pCallback" ::: Ptr DebugReportCallbackEXT)
   -> IO Result)
-> Ptr Instance_T
-> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pCallback" ::: Ptr DebugReportCallbackEXT)
-> IO Result
mkVkCreateDebugReportCallbackEXT FunPtr
  (Ptr Instance_T
   -> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pCallback" ::: Ptr DebugReportCallbackEXT)
   -> IO Result)
vkCreateDebugReportCallbackEXTPtr
  "pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
pCreateInfo <- ((("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
  -> IO DebugReportCallbackEXT)
 -> IO DebugReportCallbackEXT)
-> ContT
     DebugReportCallbackEXT
     IO
     ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
   -> IO DebugReportCallbackEXT)
  -> IO DebugReportCallbackEXT)
 -> ContT
      DebugReportCallbackEXT
      IO
      ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT))
-> ((("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
     -> IO DebugReportCallbackEXT)
    -> IO DebugReportCallbackEXT)
-> ContT
     DebugReportCallbackEXT
     IO
     ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
forall a b. (a -> b) -> a -> b
$ DebugReportCallbackCreateInfoEXT
-> (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
    -> IO DebugReportCallbackEXT)
-> IO DebugReportCallbackEXT
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DebugReportCallbackCreateInfoEXT
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT
     DebugReportCallbackEXT
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks)
  -> IO DebugReportCallbackEXT)
 -> IO DebugReportCallbackEXT)
-> ContT
     DebugReportCallbackEXT
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO DebugReportCallbackEXT)
  -> IO DebugReportCallbackEXT)
 -> ContT
      DebugReportCallbackEXT
      IO
      ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks)
     -> IO DebugReportCallbackEXT)
    -> IO DebugReportCallbackEXT)
-> ContT
     DebugReportCallbackEXT
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks)
    -> IO DebugReportCallbackEXT)
-> IO DebugReportCallbackEXT
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pCallback" ::: Ptr DebugReportCallbackEXT
pPCallback <- ((("pCallback" ::: Ptr DebugReportCallbackEXT)
  -> IO DebugReportCallbackEXT)
 -> IO DebugReportCallbackEXT)
-> ContT
     DebugReportCallbackEXT
     IO
     ("pCallback" ::: Ptr DebugReportCallbackEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCallback" ::: Ptr DebugReportCallbackEXT)
   -> IO DebugReportCallbackEXT)
  -> IO DebugReportCallbackEXT)
 -> ContT
      DebugReportCallbackEXT
      IO
      ("pCallback" ::: Ptr DebugReportCallbackEXT))
-> ((("pCallback" ::: Ptr DebugReportCallbackEXT)
     -> IO DebugReportCallbackEXT)
    -> IO DebugReportCallbackEXT)
-> ContT
     DebugReportCallbackEXT
     IO
     ("pCallback" ::: Ptr DebugReportCallbackEXT)
forall a b. (a -> b) -> a -> b
$ IO ("pCallback" ::: Ptr DebugReportCallbackEXT)
-> (("pCallback" ::: Ptr DebugReportCallbackEXT) -> IO ())
-> (("pCallback" ::: Ptr DebugReportCallbackEXT)
    -> IO DebugReportCallbackEXT)
-> IO DebugReportCallbackEXT
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pCallback" ::: Ptr DebugReportCallbackEXT)
forall a. Int -> IO (Ptr a)
callocBytes @DebugReportCallbackEXT Int
8) ("pCallback" ::: Ptr DebugReportCallbackEXT) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT DebugReportCallbackEXT IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT DebugReportCallbackEXT IO Result)
-> IO Result -> ContT DebugReportCallbackEXT IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateDebugReportCallbackEXT" (Ptr Instance_T
-> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pCallback" ::: Ptr DebugReportCallbackEXT)
-> IO Result
vkCreateDebugReportCallbackEXT' (Instance -> Ptr Instance_T
instanceHandle (Instance
instance')) "pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
pCreateInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pCallback" ::: Ptr DebugReportCallbackEXT
pPCallback))
  IO () -> ContT DebugReportCallbackEXT IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DebugReportCallbackEXT IO ())
-> IO () -> ContT DebugReportCallbackEXT IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  DebugReportCallbackEXT
pCallback <- IO DebugReportCallbackEXT
-> ContT DebugReportCallbackEXT IO DebugReportCallbackEXT
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO DebugReportCallbackEXT
 -> ContT DebugReportCallbackEXT IO DebugReportCallbackEXT)
-> IO DebugReportCallbackEXT
-> ContT DebugReportCallbackEXT IO DebugReportCallbackEXT
forall a b. (a -> b) -> a -> b
$ ("pCallback" ::: Ptr DebugReportCallbackEXT)
-> IO DebugReportCallbackEXT
forall a. Storable a => Ptr a -> IO a
peek @DebugReportCallbackEXT "pCallback" ::: Ptr DebugReportCallbackEXT
pPCallback
  DebugReportCallbackEXT
-> ContT DebugReportCallbackEXT IO DebugReportCallbackEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DebugReportCallbackEXT
 -> ContT DebugReportCallbackEXT IO DebugReportCallbackEXT)
-> DebugReportCallbackEXT
-> ContT DebugReportCallbackEXT IO DebugReportCallbackEXT
forall a b. (a -> b) -> a -> b
$ (DebugReportCallbackEXT
pCallback)

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createDebugReportCallbackEXT' and 'destroyDebugReportCallbackEXT'
--
-- To ensure that 'destroyDebugReportCallbackEXT' is always called: pass
-- 'Control.Exception.bracket' (or the allocate function from your
-- favourite resource management library) as the last argument.
-- To just extract the pair pass '(,)' as the last argument.
--
withDebugReportCallbackEXT :: forall io r . MonadIO io => Instance -> DebugReportCallbackCreateInfoEXT -> Maybe AllocationCallbacks -> (io DebugReportCallbackEXT -> (DebugReportCallbackEXT -> io ()) -> r) -> r
withDebugReportCallbackEXT :: Instance
-> DebugReportCallbackCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io DebugReportCallbackEXT
    -> (DebugReportCallbackEXT -> io ()) -> r)
-> r
withDebugReportCallbackEXT Instance
instance' DebugReportCallbackCreateInfoEXT
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator io DebugReportCallbackEXT -> (DebugReportCallbackEXT -> io ()) -> r
b =
  io DebugReportCallbackEXT -> (DebugReportCallbackEXT -> io ()) -> r
b (Instance
-> DebugReportCallbackCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io DebugReportCallbackEXT
forall (io :: * -> *).
MonadIO io =>
Instance
-> DebugReportCallbackCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io DebugReportCallbackEXT
createDebugReportCallbackEXT Instance
instance' DebugReportCallbackCreateInfoEXT
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(DebugReportCallbackEXT
o0) -> Instance
-> DebugReportCallbackEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
forall (io :: * -> *).
MonadIO io =>
Instance
-> DebugReportCallbackEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyDebugReportCallbackEXT Instance
instance' DebugReportCallbackEXT
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDestroyDebugReportCallbackEXT
  :: FunPtr (Ptr Instance_T -> DebugReportCallbackEXT -> Ptr AllocationCallbacks -> IO ()) -> Ptr Instance_T -> DebugReportCallbackEXT -> Ptr AllocationCallbacks -> IO ()

-- | vkDestroyDebugReportCallbackEXT - Destroy a debug report callback object
--
-- == Valid Usage
--
-- -   #VUID-vkDestroyDebugReportCallbackEXT-instance-01242# If
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @callback@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   #VUID-vkDestroyDebugReportCallbackEXT-instance-01243# If no
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @callback@ was created, @pAllocator@ /must/ be @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkDestroyDebugReportCallbackEXT-instance-parameter# @instance@
--     /must/ be a valid 'Vulkan.Core10.Handles.Instance' handle
--
-- -   #VUID-vkDestroyDebugReportCallbackEXT-callback-parameter# If
--     @callback@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @callback@ /must/ be a valid
--     'Vulkan.Extensions.Handles.DebugReportCallbackEXT' handle
--
-- -   #VUID-vkDestroyDebugReportCallbackEXT-pAllocator-parameter# If
--     @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid pointer
--     to a valid 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks'
--     structure
--
-- -   #VUID-vkDestroyDebugReportCallbackEXT-callback-parent# If @callback@
--     is a valid handle, it /must/ have been created, allocated, or
--     retrieved from @instance@
--
-- == Host Synchronization
--
-- -   Host access to @callback@ /must/ be externally synchronized
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_report VK_EXT_debug_report>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Extensions.Handles.DebugReportCallbackEXT',
-- 'Vulkan.Core10.Handles.Instance'
destroyDebugReportCallbackEXT :: forall io
                               . (MonadIO io)
                              => -- | @instance@ is the instance where the callback was created.
                                 Instance
                              -> -- | @callback@ is the 'Vulkan.Extensions.Handles.DebugReportCallbackEXT'
                                 -- object to destroy. @callback@ is an externally synchronized object and
                                 -- /must/ not be used on more than one thread at a time. This means that
                                 -- 'destroyDebugReportCallbackEXT' /must/ not be called when a callback is
                                 -- active.
                                 DebugReportCallbackEXT
                              -> -- | @pAllocator@ controls host memory allocation as described in the
                                 -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                                 -- chapter.
                                 ("allocator" ::: Maybe AllocationCallbacks)
                              -> io ()
destroyDebugReportCallbackEXT :: Instance
-> DebugReportCallbackEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyDebugReportCallbackEXT Instance
instance' DebugReportCallbackEXT
callback "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDestroyDebugReportCallbackEXTPtr :: FunPtr
  (Ptr Instance_T
   -> DebugReportCallbackEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyDebugReportCallbackEXTPtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> DebugReportCallbackEXT
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroyDebugReportCallbackEXT (case Instance
instance' of Instance{InstanceCmds
instanceCmds :: InstanceCmds
$sel:instanceCmds:Instance :: Instance -> InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Instance_T
   -> DebugReportCallbackEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyDebugReportCallbackEXTPtr FunPtr
  (Ptr Instance_T
   -> DebugReportCallbackEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Instance_T
      -> DebugReportCallbackEXT
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Instance_T
   -> DebugReportCallbackEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkDestroyDebugReportCallbackEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyDebugReportCallbackEXT' :: Ptr Instance_T
-> DebugReportCallbackEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyDebugReportCallbackEXT' = FunPtr
  (Ptr Instance_T
   -> DebugReportCallbackEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> Ptr Instance_T
-> DebugReportCallbackEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyDebugReportCallbackEXT FunPtr
  (Ptr Instance_T
   -> DebugReportCallbackEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyDebugReportCallbackEXTPtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDestroyDebugReportCallbackEXT" (Ptr Instance_T
-> DebugReportCallbackEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyDebugReportCallbackEXT' (Instance -> Ptr Instance_T
instanceHandle (Instance
instance')) (DebugReportCallbackEXT
callback) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDebugReportMessageEXT
  :: FunPtr (Ptr Instance_T -> DebugReportFlagsEXT -> DebugReportObjectTypeEXT -> Word64 -> CSize -> Int32 -> Ptr CChar -> Ptr CChar -> IO ()) -> Ptr Instance_T -> DebugReportFlagsEXT -> DebugReportObjectTypeEXT -> Word64 -> CSize -> Int32 -> Ptr CChar -> Ptr CChar -> IO ()

-- | vkDebugReportMessageEXT - Inject a message into a debug stream
--
-- = Description
--
-- The call will propagate through the layers and generate callback(s) as
-- indicated by the message’s flags. The parameters are passed on to the
-- callback in addition to the @pUserData@ value that was defined at the
-- time the callback was registered.
--
-- == Valid Usage
--
-- -   #VUID-vkDebugReportMessageEXT-object-01241# @object@ /must/ be a
--     Vulkan object or 'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   #VUID-vkDebugReportMessageEXT-objectType-01498# If @objectType@ is
--     not 'DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT' and @object@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @object@ /must/ be a
--     Vulkan object of the corresponding type associated with @objectType@
--     as defined in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#debug-report-object-types>
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkDebugReportMessageEXT-instance-parameter# @instance@ /must/
--     be a valid 'Vulkan.Core10.Handles.Instance' handle
--
-- -   #VUID-vkDebugReportMessageEXT-flags-parameter# @flags@ /must/ be a
--     valid combination of 'DebugReportFlagBitsEXT' values
--
-- -   #VUID-vkDebugReportMessageEXT-flags-requiredbitmask# @flags@ /must/
--     not be @0@
--
-- -   #VUID-vkDebugReportMessageEXT-objectType-parameter# @objectType@
--     /must/ be a valid 'DebugReportObjectTypeEXT' value
--
-- -   #VUID-vkDebugReportMessageEXT-pLayerPrefix-parameter# @pLayerPrefix@
--     /must/ be a null-terminated UTF-8 string
--
-- -   #VUID-vkDebugReportMessageEXT-pMessage-parameter# @pMessage@ /must/
--     be a null-terminated UTF-8 string
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_report VK_EXT_debug_report>,
-- 'DebugReportFlagsEXT', 'DebugReportObjectTypeEXT',
-- 'Vulkan.Core10.Handles.Instance'
debugReportMessageEXT :: forall io
                       . (MonadIO io)
                      => -- | @instance@ is the debug stream’s 'Vulkan.Core10.Handles.Instance'.
                         Instance
                      -> -- | @flags@ specifies the 'DebugReportFlagBitsEXT' classification of this
                         -- event\/message.
                         DebugReportFlagsEXT
                      -> -- | @objectType@ is a 'DebugReportObjectTypeEXT' specifying the type of
                         -- object being used or created at the time the event was triggered.
                         DebugReportObjectTypeEXT
                      -> -- | @object@ is the object where the issue was detected. @object@ /can/ be
                         -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' if there is no object
                         -- associated with the event.
                         ("object" ::: Word64)
                      -> -- | @location@ is an application defined value.
                         ("location" ::: Word64)
                      -> -- | @messageCode@ is an application defined value.
                         ("messageCode" ::: Int32)
                      -> -- | @pLayerPrefix@ is the abbreviation of the component making this
                         -- event\/message.
                         ("layerPrefix" ::: ByteString)
                      -> -- | @pMessage@ is a null-terminated string detailing the trigger conditions.
                         ("message" ::: ByteString)
                      -> io ()
debugReportMessageEXT :: Instance
-> DebugReportFlagsEXT
-> DebugReportObjectTypeEXT
-> ("object" ::: Word64)
-> ("object" ::: Word64)
-> ("messageCode" ::: Int32)
-> ("layerPrefix" ::: ByteString)
-> ("layerPrefix" ::: ByteString)
-> io ()
debugReportMessageEXT Instance
instance' DebugReportFlagsEXT
flags DebugReportObjectTypeEXT
objectType "object" ::: Word64
object "object" ::: Word64
location "messageCode" ::: Int32
messageCode "layerPrefix" ::: ByteString
layerPrefix "layerPrefix" ::: ByteString
message = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDebugReportMessageEXTPtr :: FunPtr
  (Ptr Instance_T
   -> DebugReportFlagsEXT
   -> DebugReportObjectTypeEXT
   -> ("object" ::: Word64)
   -> ("location" ::: CSize)
   -> ("messageCode" ::: Int32)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> IO ())
vkDebugReportMessageEXTPtr = InstanceCmds
-> FunPtr
     (Ptr Instance_T
      -> DebugReportFlagsEXT
      -> DebugReportObjectTypeEXT
      -> ("object" ::: Word64)
      -> ("location" ::: CSize)
      -> ("messageCode" ::: Int32)
      -> ("pLayerPrefix" ::: Ptr CChar)
      -> ("pLayerPrefix" ::: Ptr CChar)
      -> IO ())
pVkDebugReportMessageEXT (case Instance
instance' of Instance{InstanceCmds
instanceCmds :: InstanceCmds
$sel:instanceCmds:Instance :: Instance -> InstanceCmds
instanceCmds} -> InstanceCmds
instanceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Instance_T
   -> DebugReportFlagsEXT
   -> DebugReportObjectTypeEXT
   -> ("object" ::: Word64)
   -> ("location" ::: CSize)
   -> ("messageCode" ::: Int32)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> IO ())
vkDebugReportMessageEXTPtr FunPtr
  (Ptr Instance_T
   -> DebugReportFlagsEXT
   -> DebugReportObjectTypeEXT
   -> ("object" ::: Word64)
   -> ("location" ::: CSize)
   -> ("messageCode" ::: Int32)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> IO ())
-> FunPtr
     (Ptr Instance_T
      -> DebugReportFlagsEXT
      -> DebugReportObjectTypeEXT
      -> ("object" ::: Word64)
      -> ("location" ::: CSize)
      -> ("messageCode" ::: Int32)
      -> ("pLayerPrefix" ::: Ptr CChar)
      -> ("pLayerPrefix" ::: Ptr CChar)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Instance_T
   -> DebugReportFlagsEXT
   -> DebugReportObjectTypeEXT
   -> ("object" ::: Word64)
   -> ("location" ::: CSize)
   -> ("messageCode" ::: Int32)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkDebugReportMessageEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDebugReportMessageEXT' :: Ptr Instance_T
-> DebugReportFlagsEXT
-> DebugReportObjectTypeEXT
-> ("object" ::: Word64)
-> ("location" ::: CSize)
-> ("messageCode" ::: Int32)
-> ("pLayerPrefix" ::: Ptr CChar)
-> ("pLayerPrefix" ::: Ptr CChar)
-> IO ()
vkDebugReportMessageEXT' = FunPtr
  (Ptr Instance_T
   -> DebugReportFlagsEXT
   -> DebugReportObjectTypeEXT
   -> ("object" ::: Word64)
   -> ("location" ::: CSize)
   -> ("messageCode" ::: Int32)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> IO ())
-> Ptr Instance_T
-> DebugReportFlagsEXT
-> DebugReportObjectTypeEXT
-> ("object" ::: Word64)
-> ("location" ::: CSize)
-> ("messageCode" ::: Int32)
-> ("pLayerPrefix" ::: Ptr CChar)
-> ("pLayerPrefix" ::: Ptr CChar)
-> IO ()
mkVkDebugReportMessageEXT FunPtr
  (Ptr Instance_T
   -> DebugReportFlagsEXT
   -> DebugReportObjectTypeEXT
   -> ("object" ::: Word64)
   -> ("location" ::: CSize)
   -> ("messageCode" ::: Int32)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> ("pLayerPrefix" ::: Ptr CChar)
   -> IO ())
vkDebugReportMessageEXTPtr
  "pLayerPrefix" ::: Ptr CChar
pLayerPrefix <- ((("pLayerPrefix" ::: Ptr CChar) -> IO ()) -> IO ())
-> ContT () IO ("pLayerPrefix" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pLayerPrefix" ::: Ptr CChar) -> IO ()) -> IO ())
 -> ContT () IO ("pLayerPrefix" ::: Ptr CChar))
-> ((("pLayerPrefix" ::: Ptr CChar) -> IO ()) -> IO ())
-> ContT () IO ("pLayerPrefix" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("layerPrefix" ::: ByteString)
-> (("pLayerPrefix" ::: Ptr CChar) -> IO ()) -> IO ()
forall a.
("layerPrefix" ::: ByteString)
-> (("pLayerPrefix" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("layerPrefix" ::: ByteString
layerPrefix)
  "pLayerPrefix" ::: Ptr CChar
pMessage <- ((("pLayerPrefix" ::: Ptr CChar) -> IO ()) -> IO ())
-> ContT () IO ("pLayerPrefix" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pLayerPrefix" ::: Ptr CChar) -> IO ()) -> IO ())
 -> ContT () IO ("pLayerPrefix" ::: Ptr CChar))
-> ((("pLayerPrefix" ::: Ptr CChar) -> IO ()) -> IO ())
-> ContT () IO ("pLayerPrefix" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("layerPrefix" ::: ByteString)
-> (("pLayerPrefix" ::: Ptr CChar) -> IO ()) -> IO ()
forall a.
("layerPrefix" ::: ByteString)
-> (("pLayerPrefix" ::: Ptr CChar) -> IO a) -> IO a
useAsCString ("layerPrefix" ::: ByteString
message)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDebugReportMessageEXT" (Ptr Instance_T
-> DebugReportFlagsEXT
-> DebugReportObjectTypeEXT
-> ("object" ::: Word64)
-> ("location" ::: CSize)
-> ("messageCode" ::: Int32)
-> ("pLayerPrefix" ::: Ptr CChar)
-> ("pLayerPrefix" ::: Ptr CChar)
-> IO ()
vkDebugReportMessageEXT' (Instance -> Ptr Instance_T
instanceHandle (Instance
instance')) (DebugReportFlagsEXT
flags) (DebugReportObjectTypeEXT
objectType) ("object" ::: Word64
object) (("object" ::: Word64) -> "location" ::: CSize
CSize ("object" ::: Word64
location)) ("messageCode" ::: Int32
messageCode) "pLayerPrefix" ::: Ptr CChar
pLayerPrefix "pLayerPrefix" ::: Ptr CChar
pMessage)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- No documentation found for TopLevel "VK_STRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT"
pattern $bSTRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT :: StructureType
$mSTRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT :: forall r. StructureType -> (Void# -> r) -> (Void# -> r) -> r
STRUCTURE_TYPE_DEBUG_REPORT_CREATE_INFO_EXT = STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT


-- No documentation found for TopLevel "VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_EXT = DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT


-- No documentation found for TopLevel "VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT = DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT


-- | VkDebugReportCallbackCreateInfoEXT - Structure specifying parameters of
-- a newly created debug report callback
--
-- = Description
--
-- For each 'Vulkan.Extensions.Handles.DebugReportCallbackEXT' that is
-- created the 'DebugReportCallbackCreateInfoEXT'::@flags@ determine when
-- that 'DebugReportCallbackCreateInfoEXT'::@pfnCallback@ is called. When
-- an event happens, the implementation will do a bitwise AND of the
-- event’s 'DebugReportFlagBitsEXT' flags to each
-- 'Vulkan.Extensions.Handles.DebugReportCallbackEXT' object’s flags. For
-- each non-zero result the corresponding callback will be called. The
-- callback will come directly from the component that detected the event,
-- unless some other layer intercepts the calls for its own purposes
-- (filter them in a different way, log to a system error log, etc.).
--
-- An application /may/ receive multiple callbacks if multiple
-- 'Vulkan.Extensions.Handles.DebugReportCallbackEXT' objects were created.
-- A callback will always be executed in the same thread as the originating
-- Vulkan call.
--
-- A callback may be called from multiple threads simultaneously (if the
-- application is making Vulkan calls from multiple threads).
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'PFN_vkDebugReportCallbackEXT',
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_report VK_EXT_debug_report>,
-- 'DebugReportFlagsEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'createDebugReportCallbackEXT'
data DebugReportCallbackCreateInfoEXT = DebugReportCallbackCreateInfoEXT
  { -- | @flags@ is a bitmask of 'DebugReportFlagBitsEXT' specifying which
    -- event(s) will cause this callback to be called.
    --
    -- #VUID-VkDebugReportCallbackCreateInfoEXT-flags-parameter# @flags@ /must/
    -- be a valid combination of 'DebugReportFlagBitsEXT' values
    DebugReportCallbackCreateInfoEXT -> DebugReportFlagsEXT
flags :: DebugReportFlagsEXT
  , -- | @pfnCallback@ is the application callback function to call.
    --
    -- #VUID-VkDebugReportCallbackCreateInfoEXT-pfnCallback-parameter#
    -- @pfnCallback@ /must/ be a valid 'PFN_vkDebugReportCallbackEXT' value
    DebugReportCallbackCreateInfoEXT -> PFN_vkDebugReportCallbackEXT
pfnCallback :: PFN_vkDebugReportCallbackEXT
  , -- | @pUserData@ is user data to be passed to the callback.
    DebugReportCallbackCreateInfoEXT -> Ptr ()
userData :: Ptr ()
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DebugReportCallbackCreateInfoEXT)
#endif
deriving instance Show DebugReportCallbackCreateInfoEXT

instance ToCStruct DebugReportCallbackCreateInfoEXT where
  withCStruct :: DebugReportCallbackCreateInfoEXT
-> (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
    -> IO b)
-> IO b
withCStruct DebugReportCallbackCreateInfoEXT
x ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT) -> IO b
f = Int
-> (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
    -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT) -> IO b)
 -> IO b)
-> (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \"pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p -> ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> DebugReportCallbackCreateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p DebugReportCallbackCreateInfoEXT
x (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT) -> IO b
f "pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p)
  pokeCStruct :: ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> DebugReportCallbackCreateInfoEXT -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p DebugReportCallbackCreateInfoEXT{Ptr ()
PFN_vkDebugReportCallbackEXT
DebugReportFlagsEXT
userData :: Ptr ()
pfnCallback :: PFN_vkDebugReportCallbackEXT
flags :: DebugReportFlagsEXT
$sel:userData:DebugReportCallbackCreateInfoEXT :: DebugReportCallbackCreateInfoEXT -> Ptr ()
$sel:pfnCallback:DebugReportCallbackCreateInfoEXT :: DebugReportCallbackCreateInfoEXT -> PFN_vkDebugReportCallbackEXT
$sel:flags:DebugReportCallbackCreateInfoEXT :: DebugReportCallbackCreateInfoEXT -> DebugReportFlagsEXT
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DebugReportFlagsEXT -> DebugReportFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr DebugReportFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DebugReportFlagsEXT)) (DebugReportFlagsEXT
flags)
    Ptr PFN_vkDebugReportCallbackEXT
-> PFN_vkDebugReportCallbackEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr PFN_vkDebugReportCallbackEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr PFN_vkDebugReportCallbackEXT)) (PFN_vkDebugReportCallbackEXT
pfnCallback)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ()))) (Ptr ()
userData)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> IO b -> IO b
pokeZeroCStruct "pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_REPORT_CALLBACK_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr PFN_vkDebugReportCallbackEXT
-> PFN_vkDebugReportCallbackEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr PFN_vkDebugReportCallbackEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr PFN_vkDebugReportCallbackEXT)) (PFN_vkDebugReportCallbackEXT
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DebugReportCallbackCreateInfoEXT where
  peekCStruct :: ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> IO DebugReportCallbackCreateInfoEXT
peekCStruct "pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p = do
    DebugReportFlagsEXT
flags <- Ptr DebugReportFlagsEXT -> IO DebugReportFlagsEXT
forall a. Storable a => Ptr a -> IO a
peek @DebugReportFlagsEXT (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr DebugReportFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DebugReportFlagsEXT))
    PFN_vkDebugReportCallbackEXT
pfnCallback <- Ptr PFN_vkDebugReportCallbackEXT -> IO PFN_vkDebugReportCallbackEXT
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkDebugReportCallbackEXT (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr PFN_vkDebugReportCallbackEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr PFN_vkDebugReportCallbackEXT))
    Ptr ()
pUserData <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) (("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT
p ("pCreateInfo" ::: Ptr DebugReportCallbackCreateInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ())))
    DebugReportCallbackCreateInfoEXT
-> IO DebugReportCallbackCreateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DebugReportCallbackCreateInfoEXT
 -> IO DebugReportCallbackCreateInfoEXT)
-> DebugReportCallbackCreateInfoEXT
-> IO DebugReportCallbackCreateInfoEXT
forall a b. (a -> b) -> a -> b
$ DebugReportFlagsEXT
-> PFN_vkDebugReportCallbackEXT
-> Ptr ()
-> DebugReportCallbackCreateInfoEXT
DebugReportCallbackCreateInfoEXT
             DebugReportFlagsEXT
flags PFN_vkDebugReportCallbackEXT
pfnCallback Ptr ()
pUserData

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

instance Zero DebugReportCallbackCreateInfoEXT where
  zero :: DebugReportCallbackCreateInfoEXT
zero = DebugReportFlagsEXT
-> PFN_vkDebugReportCallbackEXT
-> Ptr ()
-> DebugReportCallbackCreateInfoEXT
DebugReportCallbackCreateInfoEXT
           DebugReportFlagsEXT
forall a. Zero a => a
zero
           PFN_vkDebugReportCallbackEXT
forall a. Zero a => a
zero
           Ptr ()
forall a. Zero a => a
zero


type DebugReportFlagsEXT = DebugReportFlagBitsEXT

-- | VkDebugReportFlagBitsEXT - Bitmask specifying events which cause a debug
-- report callback
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_report VK_EXT_debug_report>,
-- 'DebugReportFlagsEXT'
newtype DebugReportFlagBitsEXT = DebugReportFlagBitsEXT Flags
  deriving newtype (DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
(DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool)
-> (DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool)
-> Eq DebugReportFlagsEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
$c/= :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
== :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
$c== :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
Eq, Eq DebugReportFlagsEXT
Eq DebugReportFlagsEXT
-> (DebugReportFlagsEXT -> DebugReportFlagsEXT -> Ordering)
-> (DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool)
-> (DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool)
-> (DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool)
-> (DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool)
-> (DebugReportFlagsEXT
    -> DebugReportFlagsEXT -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT
    -> DebugReportFlagsEXT -> DebugReportFlagsEXT)
-> Ord DebugReportFlagsEXT
DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
DebugReportFlagsEXT -> DebugReportFlagsEXT -> Ordering
DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
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 :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
$cmin :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
max :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
$cmax :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
>= :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
$c>= :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
> :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
$c> :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
<= :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
$c<= :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
< :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
$c< :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Bool
compare :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Ordering
$ccompare :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> Ordering
$cp1Ord :: Eq DebugReportFlagsEXT
Ord, Ptr b -> Int -> IO DebugReportFlagsEXT
Ptr b -> Int -> DebugReportFlagsEXT -> IO ()
Ptr DebugReportFlagsEXT -> IO DebugReportFlagsEXT
Ptr DebugReportFlagsEXT -> Int -> IO DebugReportFlagsEXT
Ptr DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT -> IO ()
Ptr DebugReportFlagsEXT -> DebugReportFlagsEXT -> IO ()
DebugReportFlagsEXT -> Int
(DebugReportFlagsEXT -> Int)
-> (DebugReportFlagsEXT -> Int)
-> (Ptr DebugReportFlagsEXT -> Int -> IO DebugReportFlagsEXT)
-> (Ptr DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DebugReportFlagsEXT)
-> (forall b. Ptr b -> Int -> DebugReportFlagsEXT -> IO ())
-> (Ptr DebugReportFlagsEXT -> IO DebugReportFlagsEXT)
-> (Ptr DebugReportFlagsEXT -> DebugReportFlagsEXT -> IO ())
-> Storable DebugReportFlagsEXT
forall b. Ptr b -> Int -> IO DebugReportFlagsEXT
forall b. Ptr b -> Int -> DebugReportFlagsEXT -> 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 DebugReportFlagsEXT -> DebugReportFlagsEXT -> IO ()
$cpoke :: Ptr DebugReportFlagsEXT -> DebugReportFlagsEXT -> IO ()
peek :: Ptr DebugReportFlagsEXT -> IO DebugReportFlagsEXT
$cpeek :: Ptr DebugReportFlagsEXT -> IO DebugReportFlagsEXT
pokeByteOff :: Ptr b -> Int -> DebugReportFlagsEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DebugReportFlagsEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO DebugReportFlagsEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DebugReportFlagsEXT
pokeElemOff :: Ptr DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT -> IO ()
$cpokeElemOff :: Ptr DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT -> IO ()
peekElemOff :: Ptr DebugReportFlagsEXT -> Int -> IO DebugReportFlagsEXT
$cpeekElemOff :: Ptr DebugReportFlagsEXT -> Int -> IO DebugReportFlagsEXT
alignment :: DebugReportFlagsEXT -> Int
$calignment :: DebugReportFlagsEXT -> Int
sizeOf :: DebugReportFlagsEXT -> Int
$csizeOf :: DebugReportFlagsEXT -> Int
Storable, DebugReportFlagsEXT
DebugReportFlagsEXT -> Zero DebugReportFlagsEXT
forall a. a -> Zero a
zero :: DebugReportFlagsEXT
$czero :: DebugReportFlagsEXT
Zero, Eq DebugReportFlagsEXT
DebugReportFlagsEXT
Eq DebugReportFlagsEXT
-> (DebugReportFlagsEXT
    -> DebugReportFlagsEXT -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT
    -> DebugReportFlagsEXT -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT
    -> DebugReportFlagsEXT -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> DebugReportFlagsEXT
-> (Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> Bool)
-> (DebugReportFlagsEXT -> Maybe Int)
-> (DebugReportFlagsEXT -> Int)
-> (DebugReportFlagsEXT -> Bool)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT)
-> (DebugReportFlagsEXT -> Int)
-> Bits DebugReportFlagsEXT
Int -> DebugReportFlagsEXT
DebugReportFlagsEXT -> Bool
DebugReportFlagsEXT -> Int
DebugReportFlagsEXT -> Maybe Int
DebugReportFlagsEXT -> DebugReportFlagsEXT
DebugReportFlagsEXT -> Int -> Bool
DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: DebugReportFlagsEXT -> Int
$cpopCount :: DebugReportFlagsEXT -> Int
rotateR :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$crotateR :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
rotateL :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$crotateL :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
unsafeShiftR :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$cunsafeShiftR :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
shiftR :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$cshiftR :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
unsafeShiftL :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$cunsafeShiftL :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
shiftL :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$cshiftL :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
isSigned :: DebugReportFlagsEXT -> Bool
$cisSigned :: DebugReportFlagsEXT -> Bool
bitSize :: DebugReportFlagsEXT -> Int
$cbitSize :: DebugReportFlagsEXT -> Int
bitSizeMaybe :: DebugReportFlagsEXT -> Maybe Int
$cbitSizeMaybe :: DebugReportFlagsEXT -> Maybe Int
testBit :: DebugReportFlagsEXT -> Int -> Bool
$ctestBit :: DebugReportFlagsEXT -> Int -> Bool
complementBit :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$ccomplementBit :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
clearBit :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$cclearBit :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
setBit :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$csetBit :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
bit :: Int -> DebugReportFlagsEXT
$cbit :: Int -> DebugReportFlagsEXT
zeroBits :: DebugReportFlagsEXT
$czeroBits :: DebugReportFlagsEXT
rotate :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$crotate :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
shift :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
$cshift :: DebugReportFlagsEXT -> Int -> DebugReportFlagsEXT
complement :: DebugReportFlagsEXT -> DebugReportFlagsEXT
$ccomplement :: DebugReportFlagsEXT -> DebugReportFlagsEXT
xor :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
$cxor :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
.|. :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
$c.|. :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
.&. :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
$c.&. :: DebugReportFlagsEXT -> DebugReportFlagsEXT -> DebugReportFlagsEXT
$cp1Bits :: Eq DebugReportFlagsEXT
Bits, Bits DebugReportFlagsEXT
Bits DebugReportFlagsEXT
-> (DebugReportFlagsEXT -> Int)
-> (DebugReportFlagsEXT -> Int)
-> (DebugReportFlagsEXT -> Int)
-> FiniteBits DebugReportFlagsEXT
DebugReportFlagsEXT -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: DebugReportFlagsEXT -> Int
$ccountTrailingZeros :: DebugReportFlagsEXT -> Int
countLeadingZeros :: DebugReportFlagsEXT -> Int
$ccountLeadingZeros :: DebugReportFlagsEXT -> Int
finiteBitSize :: DebugReportFlagsEXT -> Int
$cfiniteBitSize :: DebugReportFlagsEXT -> Int
$cp1FiniteBits :: Bits DebugReportFlagsEXT
FiniteBits)

-- | 'DEBUG_REPORT_INFORMATION_BIT_EXT' specifies an informational message
-- such as resource details that may be handy when debugging an
-- application.
pattern $bDEBUG_REPORT_INFORMATION_BIT_EXT :: DebugReportFlagsEXT
$mDEBUG_REPORT_INFORMATION_BIT_EXT :: forall r. DebugReportFlagsEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_INFORMATION_BIT_EXT         = DebugReportFlagBitsEXT 0x00000001
-- | 'DEBUG_REPORT_WARNING_BIT_EXT' specifies use of Vulkan that /may/ expose
-- an app bug. Such cases may not be immediately harmful, such as a
-- fragment shader outputting to a location with no attachment. Other cases
-- /may/ point to behavior that is almost certainly bad when unintended
-- such as using an image whose memory has not been filled. In general if
-- you see a warning but you know that the behavior is intended\/desired,
-- then simply ignore the warning.
pattern $bDEBUG_REPORT_WARNING_BIT_EXT :: DebugReportFlagsEXT
$mDEBUG_REPORT_WARNING_BIT_EXT :: forall r. DebugReportFlagsEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_WARNING_BIT_EXT             = DebugReportFlagBitsEXT 0x00000002
-- | 'DEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT' specifies a potentially
-- non-optimal use of Vulkan, e.g. using
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearColorImage' when setting
-- 'Vulkan.Core10.Pass.AttachmentDescription'::@loadOp@ to
-- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR' would
-- have worked.
pattern $bDEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT :: DebugReportFlagsEXT
$mDEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT :: forall r. DebugReportFlagsEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT = DebugReportFlagBitsEXT 0x00000004
-- | 'DEBUG_REPORT_ERROR_BIT_EXT' specifies that the application has violated
-- a valid usage condition of the specification.
pattern $bDEBUG_REPORT_ERROR_BIT_EXT :: DebugReportFlagsEXT
$mDEBUG_REPORT_ERROR_BIT_EXT :: forall r. DebugReportFlagsEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_ERROR_BIT_EXT               = DebugReportFlagBitsEXT 0x00000008
-- | 'DEBUG_REPORT_DEBUG_BIT_EXT' specifies diagnostic information from the
-- implementation and layers.
pattern $bDEBUG_REPORT_DEBUG_BIT_EXT :: DebugReportFlagsEXT
$mDEBUG_REPORT_DEBUG_BIT_EXT :: forall r. DebugReportFlagsEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_DEBUG_BIT_EXT               = DebugReportFlagBitsEXT 0x00000010

conNameDebugReportFlagBitsEXT :: String
conNameDebugReportFlagBitsEXT :: String
conNameDebugReportFlagBitsEXT = String
"DebugReportFlagBitsEXT"

enumPrefixDebugReportFlagBitsEXT :: String
enumPrefixDebugReportFlagBitsEXT :: String
enumPrefixDebugReportFlagBitsEXT = String
"DEBUG_REPORT_"

showTableDebugReportFlagBitsEXT :: [(DebugReportFlagBitsEXT, String)]
showTableDebugReportFlagBitsEXT :: [(DebugReportFlagsEXT, String)]
showTableDebugReportFlagBitsEXT =
  [ (DebugReportFlagsEXT
DEBUG_REPORT_INFORMATION_BIT_EXT        , String
"INFORMATION_BIT_EXT")
  , (DebugReportFlagsEXT
DEBUG_REPORT_WARNING_BIT_EXT            , String
"WARNING_BIT_EXT")
  , (DebugReportFlagsEXT
DEBUG_REPORT_PERFORMANCE_WARNING_BIT_EXT, String
"PERFORMANCE_WARNING_BIT_EXT")
  , (DebugReportFlagsEXT
DEBUG_REPORT_ERROR_BIT_EXT              , String
"ERROR_BIT_EXT")
  , (DebugReportFlagsEXT
DEBUG_REPORT_DEBUG_BIT_EXT              , String
"DEBUG_BIT_EXT")
  ]

instance Show DebugReportFlagBitsEXT where
  showsPrec :: Int -> DebugReportFlagsEXT -> ShowS
showsPrec = String
-> [(DebugReportFlagsEXT, String)]
-> String
-> (DebugReportFlagsEXT -> Flags)
-> (Flags -> ShowS)
-> Int
-> DebugReportFlagsEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixDebugReportFlagBitsEXT
                            [(DebugReportFlagsEXT, String)]
showTableDebugReportFlagBitsEXT
                            String
conNameDebugReportFlagBitsEXT
                            (\(DebugReportFlagBitsEXT Flags
x) -> Flags
x)
                            (\Flags
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read DebugReportFlagBitsEXT where
  readPrec :: ReadPrec DebugReportFlagsEXT
readPrec = String
-> [(DebugReportFlagsEXT, String)]
-> String
-> (Flags -> DebugReportFlagsEXT)
-> ReadPrec DebugReportFlagsEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixDebugReportFlagBitsEXT
                          [(DebugReportFlagsEXT, String)]
showTableDebugReportFlagBitsEXT
                          String
conNameDebugReportFlagBitsEXT
                          Flags -> DebugReportFlagsEXT
DebugReportFlagBitsEXT


-- | VkDebugReportObjectTypeEXT - Specify the type of an object handle
--
-- = Description
--
-- \'
--
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DebugReportObjectTypeEXT'                                | Vulkan Handle Type                                 |
-- +===========================================================+====================================================+
-- | 'DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT'                    | Unknown\/Undefined Handle                          |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT'                   | 'Vulkan.Core10.Handles.Instance'                   |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT'            | 'Vulkan.Core10.Handles.PhysicalDevice'             |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT'                     | 'Vulkan.Core10.Handles.Device'                     |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT'                      | 'Vulkan.Core10.Handles.Queue'                      |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT'                  | 'Vulkan.Core10.Handles.Semaphore'                  |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT'             | 'Vulkan.Core10.Handles.CommandBuffer'              |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT'                      | 'Vulkan.Core10.Handles.Fence'                      |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT'              | 'Vulkan.Core10.Handles.DeviceMemory'               |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT'                     | 'Vulkan.Core10.Handles.Buffer'                     |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT'                      | 'Vulkan.Core10.Handles.Image'                      |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT'                      | 'Vulkan.Core10.Handles.Event'                      |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT'                 | 'Vulkan.Core10.Handles.QueryPool'                  |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT'                | 'Vulkan.Core10.Handles.BufferView'                 |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT'                 | 'Vulkan.Core10.Handles.ImageView'                  |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT'              | 'Vulkan.Core10.Handles.ShaderModule'               |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT'             | 'Vulkan.Core10.Handles.PipelineCache'              |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT'            | 'Vulkan.Core10.Handles.PipelineLayout'             |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT'                | 'Vulkan.Core10.Handles.RenderPass'                 |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT'                   | 'Vulkan.Core10.Handles.Pipeline'                   |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT'      | 'Vulkan.Core10.Handles.DescriptorSetLayout'        |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT'                    | 'Vulkan.Core10.Handles.Sampler'                    |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT'            | 'Vulkan.Core10.Handles.DescriptorPool'             |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT'             | 'Vulkan.Core10.Handles.DescriptorSet'              |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT'                | 'Vulkan.Core10.Handles.Framebuffer'                |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT'               | 'Vulkan.Core10.Handles.CommandPool'                |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT'                | 'Vulkan.Extensions.Handles.SurfaceKHR'             |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT'              | 'Vulkan.Extensions.Handles.SwapchainKHR'           |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT'  | 'Vulkan.Extensions.Handles.DebugReportCallbackEXT' |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT'                | 'Vulkan.Extensions.Handles.DisplayKHR'             |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT'           | 'Vulkan.Extensions.Handles.DisplayModeKHR'         |
-- +-----------------------------------------------------------+----------------------------------------------------+
-- | 'DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT' | 'Vulkan.Core11.Handles.DescriptorUpdateTemplate'   |
-- +-----------------------------------------------------------+----------------------------------------------------+
--
-- 'DebugReportObjectTypeEXT' and Vulkan Handle Relationship
--
-- Note
--
-- The primary expected use of
-- 'Vulkan.Core10.Enums.Result.ERROR_VALIDATION_FAILED_EXT' is for
-- validation layer testing. It is not expected that an application would
-- see this error code during normal use of the validation layers.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_marker VK_EXT_debug_marker>,
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_report VK_EXT_debug_report>,
-- 'Vulkan.Extensions.VK_EXT_debug_marker.DebugMarkerObjectNameInfoEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_marker.DebugMarkerObjectTagInfoEXT',
-- 'debugReportMessageEXT'
newtype DebugReportObjectTypeEXT = DebugReportObjectTypeEXT Int32
  deriving newtype (DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
(DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool)
-> (DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool)
-> Eq DebugReportObjectTypeEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
$c/= :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
== :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
$c== :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
Eq, Eq DebugReportObjectTypeEXT
Eq DebugReportObjectTypeEXT
-> (DebugReportObjectTypeEXT
    -> DebugReportObjectTypeEXT -> Ordering)
-> (DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool)
-> (DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool)
-> (DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool)
-> (DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool)
-> (DebugReportObjectTypeEXT
    -> DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT)
-> (DebugReportObjectTypeEXT
    -> DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT)
-> Ord DebugReportObjectTypeEXT
DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Ordering
DebugReportObjectTypeEXT
-> DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT
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 :: DebugReportObjectTypeEXT
-> DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT
$cmin :: DebugReportObjectTypeEXT
-> DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT
max :: DebugReportObjectTypeEXT
-> DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT
$cmax :: DebugReportObjectTypeEXT
-> DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT
>= :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
$c>= :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
> :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
$c> :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
<= :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
$c<= :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
< :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
$c< :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Bool
compare :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Ordering
$ccompare :: DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> Ordering
$cp1Ord :: Eq DebugReportObjectTypeEXT
Ord, Ptr b -> Int -> IO DebugReportObjectTypeEXT
Ptr b -> Int -> DebugReportObjectTypeEXT -> IO ()
Ptr DebugReportObjectTypeEXT -> IO DebugReportObjectTypeEXT
Ptr DebugReportObjectTypeEXT -> Int -> IO DebugReportObjectTypeEXT
Ptr DebugReportObjectTypeEXT
-> Int -> DebugReportObjectTypeEXT -> IO ()
Ptr DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> IO ()
DebugReportObjectTypeEXT -> Int
(DebugReportObjectTypeEXT -> Int)
-> (DebugReportObjectTypeEXT -> Int)
-> (Ptr DebugReportObjectTypeEXT
    -> Int -> IO DebugReportObjectTypeEXT)
-> (Ptr DebugReportObjectTypeEXT
    -> Int -> DebugReportObjectTypeEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DebugReportObjectTypeEXT)
-> (forall b. Ptr b -> Int -> DebugReportObjectTypeEXT -> IO ())
-> (Ptr DebugReportObjectTypeEXT -> IO DebugReportObjectTypeEXT)
-> (Ptr DebugReportObjectTypeEXT
    -> DebugReportObjectTypeEXT -> IO ())
-> Storable DebugReportObjectTypeEXT
forall b. Ptr b -> Int -> IO DebugReportObjectTypeEXT
forall b. Ptr b -> Int -> DebugReportObjectTypeEXT -> 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 DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> IO ()
$cpoke :: Ptr DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> IO ()
peek :: Ptr DebugReportObjectTypeEXT -> IO DebugReportObjectTypeEXT
$cpeek :: Ptr DebugReportObjectTypeEXT -> IO DebugReportObjectTypeEXT
pokeByteOff :: Ptr b -> Int -> DebugReportObjectTypeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DebugReportObjectTypeEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO DebugReportObjectTypeEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DebugReportObjectTypeEXT
pokeElemOff :: Ptr DebugReportObjectTypeEXT
-> Int -> DebugReportObjectTypeEXT -> IO ()
$cpokeElemOff :: Ptr DebugReportObjectTypeEXT
-> Int -> DebugReportObjectTypeEXT -> IO ()
peekElemOff :: Ptr DebugReportObjectTypeEXT -> Int -> IO DebugReportObjectTypeEXT
$cpeekElemOff :: Ptr DebugReportObjectTypeEXT -> Int -> IO DebugReportObjectTypeEXT
alignment :: DebugReportObjectTypeEXT -> Int
$calignment :: DebugReportObjectTypeEXT -> Int
sizeOf :: DebugReportObjectTypeEXT -> Int
$csizeOf :: DebugReportObjectTypeEXT -> Int
Storable, DebugReportObjectTypeEXT
DebugReportObjectTypeEXT -> Zero DebugReportObjectTypeEXT
forall a. a -> Zero a
zero :: DebugReportObjectTypeEXT
$czero :: DebugReportObjectTypeEXT
Zero)

-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT                    = DebugReportObjectTypeEXT 0
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT                   = DebugReportObjectTypeEXT 1
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT            = DebugReportObjectTypeEXT 2
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT                     = DebugReportObjectTypeEXT 3
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT                      = DebugReportObjectTypeEXT 4
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT                  = DebugReportObjectTypeEXT 5
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT             = DebugReportObjectTypeEXT 6
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_FENCE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_FENCE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT                      = DebugReportObjectTypeEXT 7
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT              = DebugReportObjectTypeEXT 8
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT                     = DebugReportObjectTypeEXT 9
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT                      = DebugReportObjectTypeEXT 10
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_EVENT_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_EVENT_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT                      = DebugReportObjectTypeEXT 11
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT                 = DebugReportObjectTypeEXT 12
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT                = DebugReportObjectTypeEXT 13
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT                 = DebugReportObjectTypeEXT 14
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT              = DebugReportObjectTypeEXT 15
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT             = DebugReportObjectTypeEXT 16
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT            = DebugReportObjectTypeEXT 17
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT                = DebugReportObjectTypeEXT 18
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT                   = DebugReportObjectTypeEXT 19
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT      = DebugReportObjectTypeEXT 20
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT                    = DebugReportObjectTypeEXT 21
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT            = DebugReportObjectTypeEXT 22
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT             = DebugReportObjectTypeEXT 23
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT                = DebugReportObjectTypeEXT 24
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT               = DebugReportObjectTypeEXT 25
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT                = DebugReportObjectTypeEXT 26
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT              = DebugReportObjectTypeEXT 27
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT  = DebugReportObjectTypeEXT 28
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT                = DebugReportObjectTypeEXT 29
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT           = DebugReportObjectTypeEXT 30
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT       = DebugReportObjectTypeEXT 33
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA_EXT  = DebugReportObjectTypeEXT 1000366000
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_NV_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_NV_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_NV_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_NV_EXT  = DebugReportObjectTypeEXT 1000165000
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT   = DebugReportObjectTypeEXT 1000156000
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR_EXT = DebugReportObjectTypeEXT 1000150000
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_CU_FUNCTION_NVX_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_CU_FUNCTION_NVX_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_CU_FUNCTION_NVX_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_CU_FUNCTION_NVX_EXT            = DebugReportObjectTypeEXT 1000029001
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_CU_MODULE_NVX_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_CU_MODULE_NVX_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_CU_MODULE_NVX_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_CU_MODULE_NVX_EXT              = DebugReportObjectTypeEXT 1000029000
-- No documentation found for Nested "VkDebugReportObjectTypeEXT" "VK_DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT"
pattern $bDEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT :: DebugReportObjectTypeEXT
$mDEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT :: forall r.
DebugReportObjectTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT = DebugReportObjectTypeEXT 1000085000
{-# complete DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT,
             DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT,
             DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT,
             DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT,
             DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT,
             DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT,
             DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT,
             DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT,
             DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT,
             DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT,
             DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT,
             DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT,
             DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT,
             DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT,
             DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT,
             DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT,
             DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT,
             DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT,
             DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT,
             DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT,
             DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT,
             DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT,
             DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT,
             DEBUG_REPORT_OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA_EXT,
             DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_NV_EXT,
             DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT,
             DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR_EXT,
             DEBUG_REPORT_OBJECT_TYPE_CU_FUNCTION_NVX_EXT,
             DEBUG_REPORT_OBJECT_TYPE_CU_MODULE_NVX_EXT,
             DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT :: DebugReportObjectTypeEXT #-}

conNameDebugReportObjectTypeEXT :: String
conNameDebugReportObjectTypeEXT :: String
conNameDebugReportObjectTypeEXT = String
"DebugReportObjectTypeEXT"

enumPrefixDebugReportObjectTypeEXT :: String
enumPrefixDebugReportObjectTypeEXT :: String
enumPrefixDebugReportObjectTypeEXT = String
"DEBUG_REPORT_OBJECT_TYPE_"

showTableDebugReportObjectTypeEXT :: [(DebugReportObjectTypeEXT, String)]
showTableDebugReportObjectTypeEXT :: [(DebugReportObjectTypeEXT, String)]
showTableDebugReportObjectTypeEXT =
  [ (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT                   , String
"UNKNOWN_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_INSTANCE_EXT                  , String
"INSTANCE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_PHYSICAL_DEVICE_EXT           , String
"PHYSICAL_DEVICE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_DEVICE_EXT                    , String
"DEVICE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_QUEUE_EXT                     , String
"QUEUE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_SEMAPHORE_EXT                 , String
"SEMAPHORE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_COMMAND_BUFFER_EXT            , String
"COMMAND_BUFFER_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_FENCE_EXT                     , String
"FENCE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_DEVICE_MEMORY_EXT             , String
"DEVICE_MEMORY_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_BUFFER_EXT                    , String
"BUFFER_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT                     , String
"IMAGE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_EVENT_EXT                     , String
"EVENT_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_QUERY_POOL_EXT                , String
"QUERY_POOL_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_BUFFER_VIEW_EXT               , String
"BUFFER_VIEW_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_IMAGE_VIEW_EXT                , String
"IMAGE_VIEW_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_SHADER_MODULE_EXT             , String
"SHADER_MODULE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_PIPELINE_CACHE_EXT            , String
"PIPELINE_CACHE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_PIPELINE_LAYOUT_EXT           , String
"PIPELINE_LAYOUT_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_RENDER_PASS_EXT               , String
"RENDER_PASS_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_PIPELINE_EXT                  , String
"PIPELINE_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT_EXT     , String
"DESCRIPTOR_SET_LAYOUT_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_SAMPLER_EXT                   , String
"SAMPLER_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_POOL_EXT           , String
"DESCRIPTOR_POOL_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_SET_EXT            , String
"DESCRIPTOR_SET_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_FRAMEBUFFER_EXT               , String
"FRAMEBUFFER_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_COMMAND_POOL_EXT              , String
"COMMAND_POOL_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_SURFACE_KHR_EXT               , String
"SURFACE_KHR_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_SWAPCHAIN_KHR_EXT             , String
"SWAPCHAIN_KHR_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT_EXT , String
"DEBUG_REPORT_CALLBACK_EXT_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_DISPLAY_KHR_EXT               , String
"DISPLAY_KHR_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_DISPLAY_MODE_KHR_EXT          , String
"DISPLAY_MODE_KHR_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_VALIDATION_CACHE_EXT_EXT      , String
"VALIDATION_CACHE_EXT_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA_EXT , String
"BUFFER_COLLECTION_FUCHSIA_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_NV_EXT , String
"ACCELERATION_STRUCTURE_NV_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_SAMPLER_YCBCR_CONVERSION_EXT  , String
"SAMPLER_YCBCR_CONVERSION_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR_EXT, String
"ACCELERATION_STRUCTURE_KHR_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_CU_FUNCTION_NVX_EXT           , String
"CU_FUNCTION_NVX_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_CU_MODULE_NVX_EXT             , String
"CU_MODULE_NVX_EXT")
  , (DebugReportObjectTypeEXT
DEBUG_REPORT_OBJECT_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_EXT, String
"DESCRIPTOR_UPDATE_TEMPLATE_EXT")
  ]

instance Show DebugReportObjectTypeEXT where
  showsPrec :: Int -> DebugReportObjectTypeEXT -> ShowS
showsPrec = String
-> [(DebugReportObjectTypeEXT, String)]
-> String
-> (DebugReportObjectTypeEXT -> "messageCode" ::: Int32)
-> (("messageCode" ::: Int32) -> ShowS)
-> Int
-> DebugReportObjectTypeEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixDebugReportObjectTypeEXT
                            [(DebugReportObjectTypeEXT, String)]
showTableDebugReportObjectTypeEXT
                            String
conNameDebugReportObjectTypeEXT
                            (\(DebugReportObjectTypeEXT "messageCode" ::: Int32
x) -> "messageCode" ::: Int32
x)
                            (Int -> ("messageCode" ::: Int32) -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read DebugReportObjectTypeEXT where
  readPrec :: ReadPrec DebugReportObjectTypeEXT
readPrec = String
-> [(DebugReportObjectTypeEXT, String)]
-> String
-> (("messageCode" ::: Int32) -> DebugReportObjectTypeEXT)
-> ReadPrec DebugReportObjectTypeEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixDebugReportObjectTypeEXT
                          [(DebugReportObjectTypeEXT, String)]
showTableDebugReportObjectTypeEXT
                          String
conNameDebugReportObjectTypeEXT
                          ("messageCode" ::: Int32) -> DebugReportObjectTypeEXT
DebugReportObjectTypeEXT


type FN_vkDebugReportCallbackEXT = DebugReportFlagsEXT -> DebugReportObjectTypeEXT -> ("object" ::: Word64) -> ("location" ::: CSize) -> ("messageCode" ::: Int32) -> ("pLayerPrefix" ::: Ptr CChar) -> ("pMessage" ::: Ptr CChar) -> ("pUserData" ::: Ptr ()) -> IO Bool32
-- | PFN_vkDebugReportCallbackEXT - Application-defined debug report callback
-- function
--
-- = Description
--
-- The callback /must/ not call 'destroyDebugReportCallbackEXT'.
--
-- The callback returns a 'Vulkan.Core10.FundamentalTypes.Bool32', which is
-- interpreted in a layer-specified manner. The application /should/ always
-- return 'Vulkan.Core10.FundamentalTypes.FALSE'. The
-- 'Vulkan.Core10.FundamentalTypes.TRUE' value is reserved for use in layer
-- development.
--
-- @object@ /must/ be a Vulkan object or
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE'. If @objectType@ is not
-- 'DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT' and @object@ is not
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE', @object@ /must/ be a Vulkan
-- object of the corresponding type associated with @objectType@ as defined
-- in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#debug-report-object-types>.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_report VK_EXT_debug_report>,
-- 'DebugReportCallbackCreateInfoEXT'
type PFN_vkDebugReportCallbackEXT = FunPtr FN_vkDebugReportCallbackEXT


type EXT_DEBUG_REPORT_SPEC_VERSION = 10

-- No documentation found for TopLevel "VK_EXT_DEBUG_REPORT_SPEC_VERSION"
pattern EXT_DEBUG_REPORT_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DEBUG_REPORT_SPEC_VERSION :: a
$mEXT_DEBUG_REPORT_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_DEBUG_REPORT_SPEC_VERSION = 10


type EXT_DEBUG_REPORT_EXTENSION_NAME = "VK_EXT_debug_report"

-- No documentation found for TopLevel "VK_EXT_DEBUG_REPORT_EXTENSION_NAME"
pattern EXT_DEBUG_REPORT_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DEBUG_REPORT_EXTENSION_NAME :: a
$mEXT_DEBUG_REPORT_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_DEBUG_REPORT_EXTENSION_NAME = "VK_EXT_debug_report"