{-# language CPP #-}
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 Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
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 Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
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(CFloat))
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_T)
import Vulkan.Extensions.VK_EXT_debug_report (DebugReportObjectTypeEXT)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
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)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @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
--
-- '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 :: Device -> DebugMarkerObjectNameInfoEXT -> io ()
debugMarkerSetObjectNameEXT device :: Device
device nameInfo :: DebugMarkerObjectNameInfoEXT
nameInfo = 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 vkDebugMarkerSetObjectNameEXTPtr :: FunPtr
  (Ptr Device_T
   -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
vkDebugMarkerSetObjectNameEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
pVkDebugMarkerSetObjectNameEXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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 Device_T
   -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
vkDebugMarkerSetObjectNameEXTPtr FunPtr
  (Ptr Device_T
   -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> 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 "" "The function pointer for vkDebugMarkerSetObjectNameEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- ((("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO ())
 -> IO ())
-> ContT () IO ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO ())
  -> IO ())
 -> ContT () IO ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT))
-> ((("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO ())
    -> IO ())
-> ContT () IO ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
forall a b. (a -> b) -> a -> b
$ DebugMarkerObjectNameInfoEXT
-> (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DebugMarkerObjectNameInfoEXT
nameInfo)
  Result
r <- IO Result -> ContT () IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT () IO Result)
-> IO Result -> ContT () IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO Result
vkDebugMarkerSetObjectNameEXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
pNameInfo
  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 ()
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))


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)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @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
--
-- '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 :: Device -> DebugMarkerObjectTagInfoEXT -> io ()
debugMarkerSetObjectTagEXT device :: Device
device tagInfo :: DebugMarkerObjectTagInfoEXT
tagInfo = 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 vkDebugMarkerSetObjectTagEXTPtr :: FunPtr
  (Ptr Device_T
   -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
vkDebugMarkerSetObjectTagEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
pVkDebugMarkerSetObjectTagEXT (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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 Device_T
   -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
vkDebugMarkerSetObjectTagEXTPtr FunPtr
  (Ptr Device_T
   -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> 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 "" "The function pointer for vkDebugMarkerSetObjectTagEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- ((("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO ())
 -> IO ())
-> ContT () IO ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO ())
  -> IO ())
 -> ContT () IO ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT))
-> ((("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO ())
    -> IO ())
-> ContT () IO ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
forall a b. (a -> b) -> a -> b
$ DebugMarkerObjectTagInfoEXT
-> (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DebugMarkerObjectTagInfoEXT
tagInfo)
  Result
r <- IO Result -> ContT () IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT () IO Result)
-> IO Result -> ContT () IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO Result
vkDebugMarkerSetObjectTagEXT' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
pTagInfo
  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 ()
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))


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)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pMarkerInfo@ /must/ be a valid pointer to a valid
--     'DebugMarkerMarkerInfoEXT' structure
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, or compute operations
--
-- == 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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- '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 :: CommandBuffer -> DebugMarkerMarkerInfoEXT -> io ()
cmdDebugMarkerBeginEXT commandBuffer :: CommandBuffer
commandBuffer markerInfo :: DebugMarkerMarkerInfoEXT
markerInfo = 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 vkCmdDebugMarkerBeginEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerBeginEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
pVkCmdDebugMarkerBeginEXT (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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 CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerBeginEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> 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 "" "The function pointer for vkCmdDebugMarkerBeginEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- ((("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
 -> IO ())
-> ContT () IO ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
  -> IO ())
 -> ContT () IO ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT))
-> ((("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
    -> IO ())
-> ContT () IO ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
forall a b. (a -> b) -> a -> b
$ DebugMarkerMarkerInfoEXT
-> (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DebugMarkerMarkerInfoEXT
markerInfo)
  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
$ Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ()
vkCmdDebugMarkerBeginEXT' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
pMarkerInfo
  () -> 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" 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
--
-- -   There /must/ be an outstanding 'cmdDebugMarkerBeginEXT' command
--     prior to the 'cmdDebugMarkerEndEXT' on the queue that
--     @commandBuffer@ is submitted to
--
-- -   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)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, or compute operations
--
-- == 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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdDebugMarkerEndEXT :: forall io
                      . (MonadIO io)
                     => -- | @commandBuffer@ is the command buffer into which the command is
                        -- recorded.
                        CommandBuffer
                     -> io ()
cmdDebugMarkerEndEXT :: CommandBuffer -> io ()
cmdDebugMarkerEndEXT commandBuffer :: CommandBuffer
commandBuffer = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdDebugMarkerEndEXTPtr :: FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdDebugMarkerEndEXTPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> IO ())
pVkCmdDebugMarkerEndEXT (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> IO ())
vkCmdDebugMarkerEndEXTPtr FunPtr (Ptr CommandBuffer_T -> IO ())
-> FunPtr (Ptr CommandBuffer_T -> IO ()) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> 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 "" "The function pointer for vkCmdDebugMarkerEndEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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
  Ptr CommandBuffer_T -> IO ()
vkCmdDebugMarkerEndEXT' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
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)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pMarkerInfo@ /must/ be a valid pointer to a valid
--     'DebugMarkerMarkerInfoEXT' structure
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support graphics, or compute operations
--
-- == 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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- '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 :: CommandBuffer -> DebugMarkerMarkerInfoEXT -> io ()
cmdDebugMarkerInsertEXT commandBuffer :: CommandBuffer
commandBuffer markerInfo :: DebugMarkerMarkerInfoEXT
markerInfo = 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 vkCmdDebugMarkerInsertEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerInsertEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
pVkCmdDebugMarkerInsertEXT (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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 CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
vkCmdDebugMarkerInsertEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> 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 "" "The function pointer for vkCmdDebugMarkerInsertEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
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 <- ((("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
 -> IO ())
-> ContT () IO ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
  -> IO ())
 -> ContT () IO ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT))
-> ((("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
    -> IO ())
-> ContT () IO ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
forall a b. (a -> b) -> a -> b
$ DebugMarkerMarkerInfoEXT
-> (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DebugMarkerMarkerInfoEXT
markerInfo)
  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
$ Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO ()
vkCmdDebugMarkerInsertEXT' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
pMarkerInfo
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
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
--
-- '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.
    --
    -- @objectType@ /must/ not be
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT'
    --
    -- @objectType@ /must/ be a valid
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT' value
    DebugMarkerObjectNameInfoEXT -> DebugReportObjectTypeEXT
objectType :: DebugReportObjectTypeEXT
  , -- | @object@ is the object to be named.
    --
    -- @object@ /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
    --
    -- @object@ /must/ be a Vulkan object of the type associated with
    -- @objectType@ as defined in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-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@.
    --
    -- @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 :: DebugMarkerObjectNameInfoEXT
-> (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b)
-> IO b
withCStruct x :: DebugMarkerObjectNameInfoEXT
x f :: ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b
f = Int
-> Int
-> (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b)
 -> IO b)
-> (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p -> ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> DebugMarkerObjectNameInfoEXT -> IO b -> IO b
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 :: ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> DebugMarkerObjectNameInfoEXT -> IO b -> IO b
pokeCStruct p :: "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p DebugMarkerObjectNameInfoEXT{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_NAME_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr DebugReportObjectTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DebugReportObjectTypeEXT)) (DebugReportObjectTypeEXT
objectType)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64)) (Word64
object)
    CString
pObjectName'' <- ((CString -> IO b) -> IO b) -> ContT b IO CString
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((CString -> IO b) -> IO b) -> ContT b IO CString)
-> ((CString -> IO b) -> IO b) -> ContT b IO CString
forall a b. (a -> b) -> a -> b
$ ByteString -> (CString -> IO b) -> IO b
forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString (ByteString
objectName)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CChar))) CString
pObjectName''
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT) -> IO b -> IO b
pokeZeroCStruct p :: "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_NAME_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr DebugReportObjectTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DebugReportObjectTypeEXT)) (DebugReportObjectTypeEXT
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    CString
pObjectName'' <- ((CString -> IO b) -> IO b) -> ContT b IO CString
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((CString -> IO b) -> IO b) -> ContT b IO CString)
-> ((CString -> IO b) -> IO b) -> ContT b IO CString
forall a b. (a -> b) -> a -> b
$ ByteString -> (CString -> IO b) -> IO b
forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString (ByteString
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CChar))) CString
pObjectName''
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct DebugMarkerObjectNameInfoEXT where
  peekCStruct :: ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> IO DebugMarkerObjectNameInfoEXT
peekCStruct p :: "pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p = do
    DebugReportObjectTypeEXT
objectType <- Ptr DebugReportObjectTypeEXT -> IO DebugReportObjectTypeEXT
forall a. Storable a => Ptr a -> IO a
peek @DebugReportObjectTypeEXT (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr DebugReportObjectTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DebugReportObjectTypeEXT))
    Word64
object <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64))
    ByteString
pObjectName <- CString -> IO ByteString
packCString (CString -> IO ByteString) -> IO CString -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT
p ("pNameInfo" ::: Ptr DebugMarkerObjectNameInfoEXT)
-> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CChar)))
    DebugMarkerObjectNameInfoEXT -> IO DebugMarkerObjectNameInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DebugMarkerObjectNameInfoEXT -> IO DebugMarkerObjectNameInfoEXT)
-> DebugMarkerObjectNameInfoEXT -> IO DebugMarkerObjectNameInfoEXT
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
           DebugReportObjectTypeEXT
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero
           ByteString
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
--
-- '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.
    --
    -- @objectType@ /must/ not be
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DEBUG_REPORT_OBJECT_TYPE_UNKNOWN_EXT'
    --
    -- @objectType@ /must/ be a valid
    -- 'Vulkan.Extensions.VK_EXT_debug_report.DebugReportObjectTypeEXT' value
    DebugMarkerObjectTagInfoEXT -> DebugReportObjectTypeEXT
objectType :: DebugReportObjectTypeEXT
  , -- | @object@ is the object to be tagged.
    --
    -- @object@ /must/ not be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
    --
    -- @object@ /must/ be a Vulkan object of the type associated with
    -- @objectType@ as defined in
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-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.
    --
    -- @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.
    --
    -- @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 :: DebugMarkerObjectTagInfoEXT
-> (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b)
-> IO b
withCStruct x :: DebugMarkerObjectTagInfoEXT
x f :: ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b
f = Int
-> Int
-> (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b)
 -> IO b)
-> (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p -> ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> DebugMarkerObjectTagInfoEXT -> IO b -> IO b
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 :: ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> DebugMarkerObjectTagInfoEXT -> IO b -> IO b
pokeCStruct p :: "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p DebugMarkerObjectTagInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_TAG_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr DebugReportObjectTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DebugReportObjectTypeEXT)) (DebugReportObjectTypeEXT
objectType)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64)) (Word64
object)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word64)) (Word64
tagName)
    Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
tagSize))
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr ()))) (Ptr ()
tag)
    IO b
f
  cStructSize :: Int
cStructSize = 56
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT) -> IO b -> IO b
pokeZeroCStruct p :: "pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_OBJECT_TAG_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DebugReportObjectTypeEXT -> DebugReportObjectTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr DebugReportObjectTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DebugReportObjectTypeEXT)) (DebugReportObjectTypeEXT
forall a. Zero a => a
zero)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
forall a. Zero a => a
zero))
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT
p ("pTagInfo" ::: Ptr DebugMarkerObjectTagInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr ()))) (Ptr ()
forall a. Zero a => a
zero)
    IO b
f

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

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

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


-- | VkDebugMarkerMarkerInfoEXT - Specify parameters of a command buffer
-- marker region
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- '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.
    --
    -- @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 :: DebugMarkerMarkerInfoEXT
-> (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b)
-> IO b
withCStruct x :: DebugMarkerMarkerInfoEXT
x f :: ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b
f = Int
-> Int
-> (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b)
 -> IO b)
-> (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p -> ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> DebugMarkerMarkerInfoEXT -> IO b -> IO b
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 :: ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> DebugMarkerMarkerInfoEXT -> IO b -> IO b
pokeCStruct p :: "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p DebugMarkerMarkerInfoEXT{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_MARKER_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    CString
pMarkerName'' <- ((CString -> IO b) -> IO b) -> ContT b IO CString
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((CString -> IO b) -> IO b) -> ContT b IO CString)
-> ((CString -> IO b) -> IO b) -> ContT b IO CString
forall a b. (a -> b) -> a -> b
$ ByteString -> (CString -> IO b) -> IO b
forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString (ByteString
markerName)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr CChar))) CString
pMarkerName''
    let pColor' :: Ptr CFloat
pColor' = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> Int -> Ptr (FixedArray 4 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (FixedArray 4 CFloat)))
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ case ((Float, Float, Float, Float)
color) of
      (e0 :: Float
e0, e1 :: Float
e1, e2 :: Float
e2, e3 :: Float
e3) -> do
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2))
        Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pColor' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT) -> IO b -> IO b
pokeZeroCStruct p :: "pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEBUG_MARKER_MARKER_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    CString
pMarkerName'' <- ((CString -> IO b) -> IO b) -> ContT b IO CString
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((CString -> IO b) -> IO b) -> ContT b IO CString)
-> ((CString -> IO b) -> IO b) -> ContT b IO CString
forall a b. (a -> b) -> a -> b
$ ByteString -> (CString -> IO b) -> IO b
forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString (ByteString
forall a. Monoid a => a
mempty)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT
p ("pMarkerInfo" ::: Ptr DebugMarkerMarkerInfoEXT)
-> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr CChar))) CString
pMarkerName''
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

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

instance Zero DebugMarkerMarkerInfoEXT where
  zero :: DebugMarkerMarkerInfoEXT
zero = ByteString
-> (Float, Float, Float, Float) -> DebugMarkerMarkerInfoEXT
DebugMarkerMarkerInfoEXT
           ByteString
forall a. Monoid a => a
mempty
           (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
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 :: a
$mEXT_DEBUG_MARKER_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> 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 :: a
$mEXT_DEBUG_MARKER_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_DEBUG_MARKER_EXTENSION_NAME = "VK_EXT_debug_marker"