{-# language CPP #-}
-- | = Name
--
-- VK_EXT_debug_marker - device extension
--
-- == VK_EXT_debug_marker
--
-- [__Name String__]
--     @VK_EXT_debug_marker@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     23
--
-- [__Revision__]
--     4
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_EXT_debug_report@ to be enabled for any
--         device-level functionality
--
-- [__Deprecation state__]
--
--     -   /Promoted/ to @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__]
--
--     -   Baldur Karlsson
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_debug_marker] @baldurk%0A*Here describe the issue or question you have about the VK_EXT_debug_marker extension* >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2017-01-31
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Baldur Karlsson
--
--     -   Dan Ginsburg, Valve
--
--     -   Jon Ashburn, LunarG
--
--     -   Kyle Spagnoli, NVIDIA
--
-- == Description
--
-- The @VK_EXT_debug_marker@ extension is a device extension. It introduces
-- concepts of object naming and tagging, for better tracking of Vulkan
-- objects, as well as additional commands for recording annotations of
-- named sections of a workload to aid organization and offline analysis in
-- external tools.
--
-- == New Commands
--
-- -   'cmdDebugMarkerBeginEXT'
--
-- -   'cmdDebugMarkerEndEXT'
--
-- -   'cmdDebugMarkerInsertEXT'
--
-- -   'debugMarkerSetObjectNameEXT'
--
-- -   'debugMarkerSetObjectTagEXT'
--
-- == New Structures
--
-- -   'DebugMarkerMarkerInfoEXT'
--
-- -   'DebugMarkerObjectNameInfoEXT'
--
-- -   'DebugMarkerObjectTagInfoEXT'
--
-- == New Enums
--
-- -   'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT'
--
-- == New Enum Constants
--
-- -   'EXT_DEBUG_MARKER_EXTENSION_NAME'
--
-- -   'EXT_DEBUG_MARKER_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEBUG_MARKER_MARKER_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_NAME_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_TAG_INFO_EXT'
--
-- == Examples
--
-- __Example 1__
--
-- Associate a name with an image, for easier debugging in external tools
-- or with validation layers that can print a friendly name when referring
-- to objects in error messages.
--
-- >     extern VkDevice device;
-- >     extern VkImage image;
-- >
-- >     // Must call extension functions through a function pointer:
-- >     PFN_vkDebugMarkerSetObjectNameEXT pfnDebugMarkerSetObjectNameEXT = (PFN_vkDebugMarkerSetObjectNameEXT)vkGetDeviceProcAddr(device, "vkDebugMarkerSetObjectNameEXT");
-- >
-- >     // Set a name on the image
-- >     const VkDebugMarkerObjectNameInfoEXT imageNameInfo =
-- >     {
-- >         VK_STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_NAME_INFO_EXT, // sType
-- >         NULL,                                           // pNext
-- >         VK_DEBUG_REPORT_OBJECT_TYPE_IMAGE_EXT,          // objectType
-- >         (uint64_t)image,                                // object
-- >         "Brick Diffuse Texture",                        // pObjectName
-- >     };
-- >
-- >     pfnDebugMarkerSetObjectNameEXT(device, &imageNameInfo);
-- >
-- >     // A subsequent error might print:
-- >     //   Image 'Brick Diffuse Texture' (0xc0dec0dedeadbeef) is used in a
-- >     //   command buffer with no memory bound to it.
--
-- __Example 2__
--
-- Annotating regions of a workload with naming information so that offline
-- analysis tools can display a more usable visualisation of the commands
-- submitted.
--
-- >     extern VkDevice device;
-- >     extern VkCommandBuffer commandBuffer;
-- >
-- >     // Must call extension functions through a function pointer:
-- >     PFN_vkCmdDebugMarkerBeginEXT pfnCmdDebugMarkerBeginEXT = (PFN_vkCmdDebugMarkerBeginEXT)vkGetDeviceProcAddr(device, "vkCmdDebugMarkerBeginEXT");
-- >     PFN_vkCmdDebugMarkerEndEXT pfnCmdDebugMarkerEndEXT = (PFN_vkCmdDebugMarkerEndEXT)vkGetDeviceProcAddr(device, "vkCmdDebugMarkerEndEXT");
-- >     PFN_vkCmdDebugMarkerInsertEXT pfnCmdDebugMarkerInsertEXT = (PFN_vkCmdDebugMarkerInsertEXT)vkGetDeviceProcAddr(device, "vkCmdDebugMarkerInsertEXT");
-- >
-- >     // Describe the area being rendered
-- >     const VkDebugMarkerMarkerInfoEXT houseMarker =
-- >     {
-- >         VK_STRUCTURE_TYPE_DEBUG_MARKER_MARKER_INFO_EXT, // sType
-- >         NULL,                                           // pNext
-- >         "Brick House",                                  // pMarkerName
-- >         { 1.0f, 0.0f, 0.0f, 1.0f },                     // color
-- >     };
-- >
-- >     // Start an annotated group of calls under the 'Brick House' name
-- >     pfnCmdDebugMarkerBeginEXT(commandBuffer, &houseMarker);
-- >     {
-- >         // A mutable structure for each part being rendered
-- >         VkDebugMarkerMarkerInfoEXT housePartMarker =
-- >         {
-- >             VK_STRUCTURE_TYPE_DEBUG_MARKER_MARKER_INFO_EXT, // sType
-- >             NULL,                                           // pNext
-- >             NULL,                                           // pMarkerName
-- >             { 0.0f, 0.0f, 0.0f, 0.0f },                     // color
-- >         };
-- >
-- >         // Set the name and insert the marker
-- >         housePartMarker.pMarkerName = "Walls";
-- >         pfnCmdDebugMarkerInsertEXT(commandBuffer, &housePartMarker);
-- >
-- >         // Insert the drawcall for the walls
-- >         vkCmdDrawIndexed(commandBuffer, 1000, 1, 0, 0, 0);
-- >
-- >         // Insert a recursive region for two sets of windows
-- >         housePartMarker.pMarkerName = "Windows";
-- >         pfnCmdDebugMarkerBeginEXT(commandBuffer, &housePartMarker);
-- >         {
-- >             vkCmdDrawIndexed(commandBuffer, 75, 6, 1000, 0, 0);
-- >             vkCmdDrawIndexed(commandBuffer, 100, 2, 1450, 0, 0);
-- >         }
-- >         pfnCmdDebugMarkerEndEXT(commandBuffer);
-- >
-- >         housePartMarker.pMarkerName = "Front Door";
-- >         pfnCmdDebugMarkerInsertEXT(commandBuffer, &housePartMarker);
-- >
-- >         vkCmdDrawIndexed(commandBuffer, 350, 1, 1650, 0, 0);
-- >
-- >         housePartMarker.pMarkerName = "Roof";
-- >         pfnCmdDebugMarkerInsertEXT(commandBuffer, &housePartMarker);
-- >
-- >         vkCmdDrawIndexed(commandBuffer, 500, 1, 2000, 0, 0);
-- >     }
-- >     // End the house annotation started above
-- >     pfnCmdDebugMarkerEndEXT(commandBuffer);
--
-- == Issues
--
-- 1) Should the tag or name for an object be specified using the @pNext@
-- parameter in the object’s @Vk*CreateInfo@ structure?
--
-- __RESOLVED__: No. While this fits with other Vulkan patterns and would
-- allow more type safety and future proofing against future objects, it
-- has notable downsides. In particular passing the name at @Vk*CreateInfo@
-- time does not allow renaming, prevents late binding of naming
-- information, and does not allow naming of implicitly created objects
-- such as queues and swapchain images.
--
-- 2) Should the command annotation functions 'cmdDebugMarkerBeginEXT' and
-- 'cmdDebugMarkerEndEXT' support the ability to specify a color?
--
-- __RESOLVED__: Yes. The functions have been expanded to take an optional
-- color which can be used at will by implementations consuming the command
-- buffer annotations in their visualisation.
--
-- 3) Should the functions added in this extension accept an extensible
-- structure as their parameter for a more flexible API, as opposed to
-- direct function parameters? If so, which functions?
--
-- __RESOLVED__: Yes. All functions have been modified to take a structure
-- type with extensible @pNext@ pointer, to allow future extensions to add
-- additional annotation information in the same commands.
--
-- == Version History
--
-- -   Revision 1, 2016-02-24 (Baldur Karlsson)
--
--     -   Initial draft, based on LunarG marker spec
--
-- -   Revision 2, 2016-02-26 (Baldur Karlsson)
--
--     -   Renamed Dbg to DebugMarker in function names
--
--     -   Allow markers in secondary command buffers under certain
--         circumstances
--
--     -   Minor language tweaks and edits
--
-- -   Revision 3, 2016-04-23 (Baldur Karlsson)
--
--     -   Reorganise spec layout to closer match desired organisation
--
--     -   Added optional color to markers (both regions and inserted
--         labels)
--
--     -   Changed functions to take extensible structs instead of direct
--         function parameters
--
-- -   Revision 4, 2017-01-31 (Baldur Karlsson)
--
--     -   Added explicit dependency on VK_EXT_debug_report
--
--     -   Moved definition of
--         'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT'
--         to debug report chapter.
--
--     -   Fixed typo in dates in revision history
--
-- == See Also
--
-- 'DebugMarkerMarkerInfoEXT', 'DebugMarkerObjectNameInfoEXT',
-- 'DebugMarkerObjectTagInfoEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT',
-- 'cmdDebugMarkerBeginEXT', 'cmdDebugMarkerEndEXT',
-- 'cmdDebugMarkerInsertEXT', 'debugMarkerSetObjectNameEXT',
-- 'debugMarkerSetObjectTagEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_debug_marker 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_marker  ( debugMarkerSetObjectNameEXT
                                              , debugMarkerSetObjectTagEXT
                                              , cmdDebugMarkerBeginEXT
                                              , cmdDebugMarkerEndEXT
                                              , cmdDebugMarkerInsertEXT
                                              , DebugMarkerObjectNameInfoEXT(..)
                                              , DebugMarkerObjectTagInfoEXT(..)
                                              , DebugMarkerMarkerInfoEXT(..)
                                              , EXT_DEBUG_MARKER_SPEC_VERSION
                                              , pattern EXT_DEBUG_MARKER_SPEC_VERSION
                                              , EXT_DEBUG_MARKER_EXTENSION_NAME
                                              , pattern EXT_DEBUG_MARKER_EXTENSION_NAME
                                              , DebugReportObjectTypeEXT(..)
                                              ) where

import Vulkan.CStruct.Utils (FixedArray)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.ByteString (packCString)
import Data.ByteString (useAsCString)
import Data.Coerce (coerce)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(..))
import Foreign.C.Types (CFloat(CFloat))
import Foreign.C.Types (CSize)
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 Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word64)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Extensions.VK_EXT_debug_report (DebugReportObjectTypeEXT)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDebugMarkerBeginEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDebugMarkerEndEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdDebugMarkerInsertEXT))
import Vulkan.Dynamic (DeviceCmds(pVkDebugMarkerSetObjectNameEXT))
import Vulkan.Dynamic (DeviceCmds(pVkDebugMarkerSetObjectTagEXT))
import Vulkan.Core10.Handles (Device_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_MARKER_MARKER_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_NAME_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_TAG_INFO_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.VK_EXT_debug_report (DebugReportObjectTypeEXT(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDebugMarkerSetObjectNameEXT
  :: FunPtr (Ptr Device_T -> Ptr DebugMarkerObjectNameInfoEXT -> IO Result) -> Ptr Device_T -> Ptr DebugMarkerObjectNameInfoEXT -> IO Result

-- | vkDebugMarkerSetObjectNameEXT - Give a user-friendly name to an object
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkDebugMarkerSetObjectNameEXT-device-parameter# @device@
--     /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkDebugMarkerSetObjectNameEXT-pNameInfo-parameter# @pNameInfo@
--     /must/ be a valid pointer to a valid 'DebugMarkerObjectNameInfoEXT'
--     structure
--
-- == Host Synchronization
--
-- -   Host access to @pNameInfo->object@ /must/ be externally synchronized
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_marker VK_EXT_debug_marker>,
-- 'DebugMarkerObjectNameInfoEXT', 'Vulkan.Core10.Handles.Device'
debugMarkerSetObjectNameEXT :: forall io
                             . (MonadIO io)
                            => -- | @device@ is the device that created the object.
                               Device
                            -> -- | @pNameInfo@ is a pointer to a 'DebugMarkerObjectNameInfoEXT' structure
                               -- specifying the parameters of the name to set on the object.
                               DebugMarkerObjectNameInfoEXT
                            -> io ()
debugMarkerSetObjectNameEXT :: forall (io :: * -> *).
MonadIO io =>
Device -> DebugMarkerObjectNameInfoEXT -> io ()
debugMarkerSetObjectNameEXT Device
device DebugMarkerObjectNameInfoEXT
nameInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkDebugMarkerSetObjectNameEXTPtr :: FunPtr
  (Ptr Device_T
   -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
vkDebugMarkerSetObjectNameEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
pVkDebugMarkerSetObjectNameEXT (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
vkDebugMarkerSetObjectNameEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkDebugMarkerSetObjectNameEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkDebugMarkerSetObjectNameEXT' :: Ptr Device_T
-> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result
vkDebugMarkerSetObjectNameEXT' = FunPtr
  (Ptr Device_T
   -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
-> Ptr Device_T
-> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> IO Result
mkVkDebugMarkerSetObjectNameEXT FunPtr
  (Ptr Device_T
   -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
vkDebugMarkerSetObjectNameEXTPtr
  "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
pNameInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DebugMarkerObjectNameInfoEXT
nameInfo)
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDebugMarkerSetObjectNameEXT" (Ptr Device_T
-> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result
vkDebugMarkerSetObjectNameEXT'
                                                                  (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                  "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
pNameInfo)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))


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

-- | vkDebugMarkerSetObjectTagEXT - Attach arbitrary data to an object
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkDebugMarkerSetObjectTagEXT-device-parameter# @device@ /must/
--     be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkDebugMarkerSetObjectTagEXT-pTagInfo-parameter# @pTagInfo@
--     /must/ be a valid pointer to a valid 'DebugMarkerObjectTagInfoEXT'
--     structure
--
-- == Host Synchronization
--
-- -   Host access to @pTagInfo->object@ /must/ be externally synchronized
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_marker VK_EXT_debug_marker>,
-- 'DebugMarkerObjectTagInfoEXT', 'Vulkan.Core10.Handles.Device'
debugMarkerSetObjectTagEXT :: forall io
                            . (MonadIO io)
                           => -- | @device@ is the device that created the object.
                              Device
                           -> -- | @pTagInfo@ is a pointer to a 'DebugMarkerObjectTagInfoEXT' structure
                              -- specifying the parameters of the tag to attach to the object.
                              DebugMarkerObjectTagInfoEXT
                           -> io ()
debugMarkerSetObjectTagEXT :: forall (io :: * -> *).
MonadIO io =>
Device -> DebugMarkerObjectTagInfoEXT -> io ()
debugMarkerSetObjectTagEXT Device
device DebugMarkerObjectTagInfoEXT
tagInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkDebugMarkerSetObjectTagEXTPtr :: FunPtr
  (Ptr Device_T
   -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
vkDebugMarkerSetObjectTagEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
pVkDebugMarkerSetObjectTagEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
vkDebugMarkerSetObjectTagEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkDebugMarkerSetObjectTagEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkDebugMarkerSetObjectTagEXT' :: Ptr Device_T
-> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result
vkDebugMarkerSetObjectTagEXT' = FunPtr
  (Ptr Device_T
   -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
-> Ptr Device_T
-> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> IO Result
mkVkDebugMarkerSetObjectTagEXT FunPtr
  (Ptr Device_T
   -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
vkDebugMarkerSetObjectTagEXTPtr
  "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
pTagInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DebugMarkerObjectTagInfoEXT
tagInfo)
  Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDebugMarkerSetObjectTagEXT" (Ptr Device_T
-> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result
vkDebugMarkerSetObjectTagEXT'
                                                                 (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                 "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
pTagInfo)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdDebugMarkerBeginEXT
  :: FunPtr (Ptr CommandBuffer_T -> Ptr DebugMarkerMarkerInfoEXT -> IO ()) -> Ptr CommandBuffer_T -> Ptr DebugMarkerMarkerInfoEXT -> IO ()

-- | vkCmdDebugMarkerBeginEXT - Open a command buffer marker region
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdDebugMarkerBeginEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdDebugMarkerBeginEXT-pMarkerInfo-parameter# @pMarkerInfo@
--     /must/ be a valid pointer to a valid 'DebugMarkerMarkerInfoEXT'
--     structure
--
-- -   #VUID-vkCmdDebugMarkerBeginEXT-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdDebugMarkerBeginEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, or compute operations
--
-- -   #VUID-vkCmdDebugMarkerBeginEXT-videocoding# This command /must/ only
--     be called outside of a video coding scope
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Outside                                                                                                                     | Graphics                                                                                                              | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             | Compute                                                                                                               |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_marker VK_EXT_debug_marker>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'DebugMarkerMarkerInfoEXT'
cmdDebugMarkerBeginEXT :: forall io
                        . (MonadIO io)
                       => -- | @commandBuffer@ is the command buffer into which the command is
                          -- recorded.
                          CommandBuffer
                       -> -- | @pMarkerInfo@ is a pointer to a 'DebugMarkerMarkerInfoEXT' structure
                          -- specifying the parameters of the marker region to open.
                          DebugMarkerMarkerInfoEXT
                       -> io ()
cmdDebugMarkerBeginEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> DebugMarkerMarkerInfoEXT -> io ()
cmdDebugMarkerBeginEXT CommandBuffer
commandBuffer DebugMarkerMarkerInfoEXT
markerInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkCmdDebugMarkerBeginEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerBeginEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
pVkCmdDebugMarkerBeginEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerBeginEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCmdDebugMarkerBeginEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdDebugMarkerBeginEXT' :: Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ()
vkCmdDebugMarkerBeginEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
-> Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> IO ()
mkVkCmdDebugMarkerBeginEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerBeginEXTPtr
  "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
pMarkerInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DebugMarkerMarkerInfoEXT
markerInfo)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdDebugMarkerBeginEXT" (Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ()
vkCmdDebugMarkerBeginEXT'
                                                        (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                        "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
pMarkerInfo)
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdDebugMarkerEndEXT
  :: FunPtr (Ptr CommandBuffer_T -> IO ()) -> Ptr CommandBuffer_T -> IO ()

-- | vkCmdDebugMarkerEndEXT - Close a command buffer marker region
--
-- = Description
--
-- An application /may/ open a marker region in one command buffer and
-- close it in another, or otherwise split marker regions across multiple
-- command buffers or multiple queue submissions. When viewed from the
-- linear series of submissions to a single queue, the calls to
-- 'cmdDebugMarkerBeginEXT' and 'cmdDebugMarkerEndEXT' /must/ be matched
-- and balanced.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdDebugMarkerEndEXT-commandBuffer-01239# There /must/ be an
--     outstanding 'cmdDebugMarkerBeginEXT' command prior to the
--     'cmdDebugMarkerEndEXT' on the queue that @commandBuffer@ is
--     submitted to
--
-- -   #VUID-vkCmdDebugMarkerEndEXT-commandBuffer-01240# If @commandBuffer@
--     is a secondary command buffer, there /must/ be an outstanding
--     'cmdDebugMarkerBeginEXT' command recorded to @commandBuffer@ that
--     has not previously been ended by a call to 'cmdDebugMarkerEndEXT'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdDebugMarkerEndEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdDebugMarkerEndEXT-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdDebugMarkerEndEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, or compute operations
--
-- -   #VUID-vkCmdDebugMarkerEndEXT-videocoding# This command /must/ only
--     be called outside of a video coding scope
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Outside                                                                                                                     | Graphics                                                                                                              | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             | Compute                                                                                                               |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_marker VK_EXT_debug_marker>,
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdDebugMarkerEndEXT :: forall io
                      . (MonadIO io)
                     => -- | @commandBuffer@ is the command buffer into which the command is
                        -- recorded.
                        CommandBuffer
                     -> io ()
cmdDebugMarkerEndEXT :: forall (io :: * -> *). MonadIO io => CommandBuffer -> io ()
cmdDebugMarkerEndEXT CommandBuffer
commandBuffer = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
  let vkCmdDebugMarkerEndEXTPtr :: FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdDebugMarkerEndEXTPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> IO ())
pVkCmdDebugMarkerEndEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdDebugMarkerEndEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCmdDebugMarkerEndEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdDebugMarkerEndEXT' :: Ptr CommandBuffer_T -> IO ()
vkCmdDebugMarkerEndEXT' = FunPtr (Ptr CommandBuffer_T -> IO ())
-> Ptr CommandBuffer_T -> IO ()
mkVkCmdDebugMarkerEndEXT FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdDebugMarkerEndEXTPtr
  forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdDebugMarkerEndEXT" (Ptr CommandBuffer_T -> IO ()
vkCmdDebugMarkerEndEXT'
                                               (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)))
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdDebugMarkerInsertEXT
  :: FunPtr (Ptr CommandBuffer_T -> Ptr DebugMarkerMarkerInfoEXT -> IO ()) -> Ptr CommandBuffer_T -> Ptr DebugMarkerMarkerInfoEXT -> IO ()

-- | vkCmdDebugMarkerInsertEXT - Insert a marker label into a command buffer
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdDebugMarkerInsertEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdDebugMarkerInsertEXT-pMarkerInfo-parameter# @pMarkerInfo@
--     /must/ be a valid pointer to a valid 'DebugMarkerMarkerInfoEXT'
--     structure
--
-- -   #VUID-vkCmdDebugMarkerInsertEXT-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdDebugMarkerInsertEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, or compute operations
--
-- -   #VUID-vkCmdDebugMarkerInsertEXT-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Outside                                                                                                                     | Graphics                                                                                                              | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             | Compute                                                                                                               |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_marker VK_EXT_debug_marker>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'DebugMarkerMarkerInfoEXT'
cmdDebugMarkerInsertEXT :: forall io
                         . (MonadIO io)
                        => -- | @commandBuffer@ is the command buffer into which the command is
                           -- recorded.
                           CommandBuffer
                        -> -- | @pMarkerInfo@ is a pointer to a 'DebugMarkerMarkerInfoEXT' structure
                           -- specifying the parameters of the marker to insert.
                           DebugMarkerMarkerInfoEXT
                        -> io ()
cmdDebugMarkerInsertEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> DebugMarkerMarkerInfoEXT -> io ()
cmdDebugMarkerInsertEXT CommandBuffer
commandBuffer DebugMarkerMarkerInfoEXT
markerInfo = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
  let vkCmdDebugMarkerInsertEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerInsertEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
pVkCmdDebugMarkerInsertEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerInsertEXTPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
    forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCmdDebugMarkerInsertEXT is null" forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  let vkCmdDebugMarkerInsertEXT' :: Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ()
vkCmdDebugMarkerInsertEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
-> Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> IO ()
mkVkCmdDebugMarkerInsertEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerInsertEXTPtr
  "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
pMarkerInfo <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DebugMarkerMarkerInfoEXT
markerInfo)
  forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdDebugMarkerInsertEXT" (Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ()
vkCmdDebugMarkerInsertEXT'
                                                         (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                         "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
pMarkerInfo)
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ()


-- | VkDebugMarkerObjectNameInfoEXT - Specify parameters of a name to give to
-- an object
--
-- = Description
--
-- Applications /may/ change the name associated with an object simply by
-- calling 'debugMarkerSetObjectNameEXT' again with a new string. To remove
-- a previously set name, @pObjectName@ /should/ be set to an empty string.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_marker VK_EXT_debug_marker>,
-- 'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'debugMarkerSetObjectNameEXT'
data DebugMarkerObjectNameInfoEXT = DebugMarkerObjectNameInfoEXT
  { -- | @objectType@ is a
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT'
    -- specifying the type of the object to be named.
    --
    -- #VUID-VkDebugMarkerObjectNameInfoEXT-objectType-01490# @objectType@
    -- /must/ not be
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT'
    --
    -- #VUID-VkDebugMarkerObjectNameInfoEXT-objectType-parameter# @objectType@
    -- /must/ be a valid
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT' value
    DebugMarkerObjectNameInfoEXT -> DebugReportObjectTypeEXT
objectType :: DebugReportObjectTypeEXT
  , -- | @object@ is the object to be named.
    --
    -- #VUID-VkDebugMarkerObjectNameInfoEXT-object-01491# @object@ /must/ not
    -- be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
    --
    -- #VUID-VkDebugMarkerObjectNameInfoEXT-object-01492# @object@ /must/ be a
    -- Vulkan object of the type associated with @objectType@ as defined in
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#debug-report-object-types>
    DebugMarkerObjectNameInfoEXT -> Word64
object :: Word64
  , -- | @pObjectName@ is a null-terminated UTF-8 string specifying the name to
    -- apply to @object@.
    --
    -- #VUID-VkDebugMarkerObjectNameInfoEXT-pObjectName-parameter#
    -- @pObjectName@ /must/ be a null-terminated UTF-8 string
    DebugMarkerObjectNameInfoEXT -> ByteString
objectName :: ByteString
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DebugMarkerObjectNameInfoEXT)
#endif
deriving instance Show DebugMarkerObjectNameInfoEXT

instance ToCStruct DebugMarkerObjectNameInfoEXT where
  withCStruct :: forall b.
DebugMarkerObjectNameInfoEXT
-> (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b)
-> IO b
withCStruct DebugMarkerObjectNameInfoEXT
x ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p DebugMarkerObjectNameInfoEXT
x (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b
f "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p)
  pokeCStruct :: forall b.
("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> DebugMarkerObjectNameInfoEXT -> IO b -> IO b
pokeCStruct "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p DebugMarkerObjectNameInfoEXT{Word64
ByteString
DebugReportObjectTypeEXT
objectName :: ByteString
object :: Word64
objectType :: DebugReportObjectTypeEXT
$sel:objectName:DebugMarkerObjectNameInfoEXT :: DebugMarkerObjectNameInfoEXT -> ByteString
$sel:object:DebugMarkerObjectNameInfoEXT :: DebugMarkerObjectNameInfoEXT -> Word64
$sel:objectType:DebugMarkerObjectNameInfoEXT :: DebugMarkerObjectNameInfoEXT -> DebugReportObjectTypeEXT
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_NAME_INFO_EXT)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DebugReportObjectTypeEXT)) (DebugReportObjectTypeEXT
objectType)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
object)
    Ptr CChar
pObjectName'' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
useAsCString (ByteString
objectName)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr CChar))) Ptr CChar
pObjectName''
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_NAME_INFO_EXT)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DebugReportObjectTypeEXT)) (forall a. Zero a => a
zero)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (forall a. Zero a => a
zero)
    Ptr CChar
pObjectName'' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
useAsCString (forall a. Monoid a => a
mempty)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr CChar))) Ptr CChar
pObjectName''
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct DebugMarkerObjectNameInfoEXT where
  peekCStruct :: ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> IO DebugMarkerObjectNameInfoEXT
peekCStruct "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p = do
    DebugReportObjectTypeEXT
objectType <- forall a. Storable a => Ptr a -> IO a
peek @DebugReportObjectTypeEXT (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DebugReportObjectTypeEXT))
    Word64
object <- forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
    ByteString
pObjectName <- Ptr CChar -> IO ByteString
packCString forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Storable a => Ptr a -> IO a
peek (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr CChar)))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DebugReportObjectTypeEXT
-> Word64 -> ByteString -> DebugMarkerObjectNameInfoEXT
DebugMarkerObjectNameInfoEXT
             DebugReportObjectTypeEXT
objectType Word64
object ByteString
pObjectName

instance Zero DebugMarkerObjectNameInfoEXT where
  zero :: DebugMarkerObjectNameInfoEXT
zero = DebugReportObjectTypeEXT
-> Word64 -> ByteString -> DebugMarkerObjectNameInfoEXT
DebugMarkerObjectNameInfoEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Monoid a => a
mempty


-- | VkDebugMarkerObjectTagInfoEXT - Specify parameters of a tag to attach to
-- an object
--
-- = Description
--
-- The @tagName@ parameter gives a name or identifier to the type of data
-- being tagged. This can be used by debugging layers to easily filter for
-- only data that can be used by that implementation.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_marker VK_EXT_debug_marker>,
-- 'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'debugMarkerSetObjectTagEXT'
data DebugMarkerObjectTagInfoEXT = DebugMarkerObjectTagInfoEXT
  { -- | @objectType@ is a
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT'
    -- specifying the type of the object to be named.
    --
    -- #VUID-VkDebugMarkerObjectTagInfoEXT-objectType-01493# @objectType@
    -- /must/ not be
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT'
    --
    -- #VUID-VkDebugMarkerObjectTagInfoEXT-objectType-parameter# @objectType@
    -- /must/ be a valid
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT' value
    DebugMarkerObjectTagInfoEXT -> DebugReportObjectTypeEXT
objectType :: DebugReportObjectTypeEXT
  , -- | @object@ is the object to be tagged.
    --
    -- #VUID-VkDebugMarkerObjectTagInfoEXT-object-01494# @object@ /must/ not be
    -- 'Vulkan.Core10.APIConstants.NULL_HANDLE'
    --
    -- #VUID-VkDebugMarkerObjectTagInfoEXT-object-01495# @object@ /must/ be a
    -- Vulkan object of the type associated with @objectType@ as defined in
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#debug-report-object-types>
    DebugMarkerObjectTagInfoEXT -> Word64
object :: Word64
  , -- | @tagName@ is a numerical identifier of the tag.
    DebugMarkerObjectTagInfoEXT -> Word64
tagName :: Word64
  , -- | @tagSize@ is the number of bytes of data to attach to the object.
    --
    -- #VUID-VkDebugMarkerObjectTagInfoEXT-tagSize-arraylength# @tagSize@
    -- /must/ be greater than @0@
    DebugMarkerObjectTagInfoEXT -> Word64
tagSize :: Word64
  , -- | @pTag@ is a pointer to an array of @tagSize@ bytes containing the data
    -- to be associated with the object.
    --
    -- #VUID-VkDebugMarkerObjectTagInfoEXT-pTag-parameter# @pTag@ /must/ be a
    -- valid pointer to an array of @tagSize@ bytes
    DebugMarkerObjectTagInfoEXT -> Ptr ()
tag :: Ptr ()
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DebugMarkerObjectTagInfoEXT)
#endif
deriving instance Show DebugMarkerObjectTagInfoEXT

instance ToCStruct DebugMarkerObjectTagInfoEXT where
  withCStruct :: forall b.
DebugMarkerObjectTagInfoEXT
-> (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b)
-> IO b
withCStruct DebugMarkerObjectTagInfoEXT
x ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
56 forall a b. (a -> b) -> a -> b
$ \"pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p DebugMarkerObjectTagInfoEXT
x (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b
f "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p)
  pokeCStruct :: forall b.
("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> DebugMarkerObjectTagInfoEXT -> IO b -> IO b
pokeCStruct "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p DebugMarkerObjectTagInfoEXT{Word64
Ptr ()
DebugReportObjectTypeEXT
tag :: Ptr ()
tagSize :: Word64
tagName :: Word64
object :: Word64
objectType :: DebugReportObjectTypeEXT
$sel:tag:DebugMarkerObjectTagInfoEXT :: DebugMarkerObjectTagInfoEXT -> Ptr ()
$sel:tagSize:DebugMarkerObjectTagInfoEXT :: DebugMarkerObjectTagInfoEXT -> Word64
$sel:tagName:DebugMarkerObjectTagInfoEXT :: DebugMarkerObjectTagInfoEXT -> Word64
$sel:object:DebugMarkerObjectTagInfoEXT :: DebugMarkerObjectTagInfoEXT -> Word64
$sel:objectType:DebugMarkerObjectTagInfoEXT :: DebugMarkerObjectTagInfoEXT -> DebugReportObjectTypeEXT
..} IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_TAG_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DebugReportObjectTypeEXT)) (DebugReportObjectTypeEXT
objectType)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
object)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word64)) (Word64
tagName)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
tagSize))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr (Ptr ()))) (Ptr ()
tag)
    IO b
f
  cStructSize :: Int
cStructSize = Int
56
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p IO b
f = do
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_TAG_INFO_EXT)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DebugReportObjectTypeEXT)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word64)) (forall a. Zero a => a
zero)
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr CSize)) (Word64 -> CSize
CSize (forall a. Zero a => a
zero))
    forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr (Ptr ()))) (forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DebugMarkerObjectTagInfoEXT where
  peekCStruct :: ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> IO DebugMarkerObjectTagInfoEXT
peekCStruct "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p = do
    DebugReportObjectTypeEXT
objectType <- forall a. Storable a => Ptr a -> IO a
peek @DebugReportObjectTypeEXT (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DebugReportObjectTypeEXT))
    Word64
object <- forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
    Word64
tagName <- forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Word64))
    CSize
tagSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr CSize))
    Ptr ()
pTag <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr (Ptr ())))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DebugReportObjectTypeEXT
-> Word64
-> Word64
-> Word64
-> Ptr ()
-> DebugMarkerObjectTagInfoEXT
DebugMarkerObjectTagInfoEXT
             DebugReportObjectTypeEXT
objectType Word64
object Word64
tagName (coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 CSize
tagSize) Ptr ()
pTag

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

instance Zero DebugMarkerObjectTagInfoEXT where
  zero :: DebugMarkerObjectTagInfoEXT
zero = DebugReportObjectTypeEXT
-> Word64
-> Word64
-> Word64
-> Ptr ()
-> DebugMarkerObjectTagInfoEXT
DebugMarkerObjectTagInfoEXT
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero
           forall a. Zero a => a
zero


-- | VkDebugMarkerMarkerInfoEXT - Specify parameters of a command buffer
-- marker region
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_marker VK_EXT_debug_marker>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdDebugMarkerBeginEXT', 'cmdDebugMarkerInsertEXT'
data DebugMarkerMarkerInfoEXT = DebugMarkerMarkerInfoEXT
  { -- | @pMarkerName@ is a pointer to a null-terminated UTF-8 string containing
    -- the name of the marker.
    --
    -- #VUID-VkDebugMarkerMarkerInfoEXT-pMarkerName-parameter# @pMarkerName@
    -- /must/ be a null-terminated UTF-8 string
    DebugMarkerMarkerInfoEXT -> ByteString
markerName :: ByteString
  , -- | @color@ is an /optional/ RGBA color value that can be associated with
    -- the marker. A particular implementation /may/ choose to ignore this
    -- color value. The values contain RGBA values in order, in the range 0.0
    -- to 1.0. If all elements in @color@ are set to 0.0 then it is ignored.
    DebugMarkerMarkerInfoEXT -> (Float, Float, Float, Float)
color :: (Float, Float, Float, Float)
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DebugMarkerMarkerInfoEXT)
#endif
deriving instance Show DebugMarkerMarkerInfoEXT

instance ToCStruct DebugMarkerMarkerInfoEXT where
  withCStruct :: forall b.
DebugMarkerMarkerInfoEXT
-> (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b)
-> IO b
withCStruct DebugMarkerMarkerInfoEXT
x ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p DebugMarkerMarkerInfoEXT
x (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b
f "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p)
  pokeCStruct :: forall b.
("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> DebugMarkerMarkerInfoEXT -> IO b -> IO b
pokeCStruct "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p DebugMarkerMarkerInfoEXT{(Float, Float, Float, Float)
ByteString
color :: (Float, Float, Float, Float)
markerName :: ByteString
$sel:color:DebugMarkerMarkerInfoEXT :: DebugMarkerMarkerInfoEXT -> (Float, Float, Float, Float)
$sel:markerName:DebugMarkerMarkerInfoEXT :: DebugMarkerMarkerInfoEXT -> ByteString
..} IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_MARKER_INFO_EXT)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    Ptr CChar
pMarkerName'' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
useAsCString (ByteString
markerName)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr CChar))) Ptr CChar
pMarkerName''
    let pColor' :: Ptr CFloat
pColor' = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (FixedArray 4 CFloat)))
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ case ((Float, Float, Float, Float)
color) of
      (Float
e0, Float
e1, Float
e2, Float
e3) -> do
        forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
        forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2))
        forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p IO b
f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT forall a b. (a -> b) -> a -> b
$ do
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_MARKER_INFO_EXT)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
    Ptr CChar
pMarkerName'' <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
useAsCString (forall a. Monoid a => a
mempty)
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr CChar))) Ptr CChar
pMarkerName''
    let pColor' :: Ptr CFloat
pColor' = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (FixedArray 4 CFloat)))
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ case ((forall a. Zero a => a
zero, forall a. Zero a => a
zero, forall a. Zero a => a
zero, forall a. Zero a => a
zero)) of
      (Float
e0, Float
e1, Float
e2, Float
e3) -> do
        forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
        forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2))
        forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
    forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct DebugMarkerMarkerInfoEXT where
  peekCStruct :: ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> IO DebugMarkerMarkerInfoEXT
peekCStruct "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p = do
    ByteString
pMarkerName <- Ptr CChar -> IO ByteString
packCString forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Storable a => Ptr a -> IO a
peek (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr CChar)))
    let pcolor :: Ptr CFloat
pcolor = forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @CFloat (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr (FixedArray 4 CFloat)))
    CFloat
color0 <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pcolor forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` Int
0 :: Ptr CFloat))
    CFloat
color1 <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pcolor forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` Int
4 :: Ptr CFloat))
    CFloat
color2 <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pcolor forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` Int
8 :: Ptr CFloat))
    CFloat
color3 <- forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pcolor forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` Int
12 :: Ptr CFloat))
    forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ ByteString
-> (Float, Float, Float, Float) -> DebugMarkerMarkerInfoEXT
DebugMarkerMarkerInfoEXT
             ByteString
pMarkerName
             (( (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
color0)
              , (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
color1)
              , (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
color2)
              , (coerce :: forall a b. Coercible a b => a -> b
coerce @CFloat @Float CFloat
color3) ))

instance Zero DebugMarkerMarkerInfoEXT where
  zero :: DebugMarkerMarkerInfoEXT
zero = ByteString
-> (Float, Float, Float, Float) -> DebugMarkerMarkerInfoEXT
DebugMarkerMarkerInfoEXT
           forall a. Monoid a => a
mempty
           (forall a. Zero a => a
zero, forall a. Zero a => a
zero, forall a. Zero a => a
zero, forall a. Zero a => a
zero)


type EXT_DEBUG_MARKER_SPEC_VERSION = 4

-- No documentation found for TopLevel "VK_EXT_DEBUG_MARKER_SPEC_VERSION"
pattern EXT_DEBUG_MARKER_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DEBUG_MARKER_SPEC_VERSION :: forall a. Integral a => a
$mEXT_DEBUG_MARKER_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DEBUG_MARKER_SPEC_VERSION = 4


type EXT_DEBUG_MARKER_EXTENSION_NAME = "VK_EXT_debug_marker"

-- No documentation found for TopLevel "VK_EXT_DEBUG_MARKER_EXTENSION_NAME"
pattern EXT_DEBUG_MARKER_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DEBUG_MARKER_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_DEBUG_MARKER_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
EXT_DEBUG_MARKER_EXTENSION_NAME = "VK_EXT_debug_marker"