{-# language CPP #-}
module Vulkan.Extensions.VK_INTEL_performance_query  ( initializePerformanceApiINTEL
                                                     , uninitializePerformanceApiINTEL
                                                     , cmdSetPerformanceMarkerINTEL
                                                     , cmdSetPerformanceStreamMarkerINTEL
                                                     , cmdSetPerformanceOverrideINTEL
                                                     , acquirePerformanceConfigurationINTEL
                                                     , releasePerformanceConfigurationINTEL
                                                     , queueSetPerformanceConfigurationINTEL
                                                     , getPerformanceParameterINTEL
                                                     , pattern STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL
                                                     , PerformanceValueINTEL(..)
                                                     , InitializePerformanceApiInfoINTEL(..)
                                                     , QueryPoolPerformanceQueryCreateInfoINTEL(..)
                                                     , PerformanceMarkerInfoINTEL(..)
                                                     , PerformanceStreamMarkerInfoINTEL(..)
                                                     , PerformanceOverrideInfoINTEL(..)
                                                     , PerformanceConfigurationAcquireInfoINTEL(..)
                                                     , PerformanceValueDataINTEL(..)
                                                     , peekPerformanceValueDataINTEL
                                                     , PerformanceConfigurationTypeINTEL( PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL
                                                                                        , ..
                                                                                        )
                                                     , QueryPoolSamplingModeINTEL( QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL
                                                                                 , ..
                                                                                 )
                                                     , PerformanceOverrideTypeINTEL( PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL
                                                                                   , PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL
                                                                                   , ..
                                                                                   )
                                                     , PerformanceParameterTypeINTEL( PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL
                                                                                    , PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL
                                                                                    , ..
                                                                                    )
                                                     , PerformanceValueTypeINTEL( PERFORMANCE_VALUE_TYPE_UINT32_INTEL
                                                                                , PERFORMANCE_VALUE_TYPE_UINT64_INTEL
                                                                                , PERFORMANCE_VALUE_TYPE_FLOAT_INTEL
                                                                                , PERFORMANCE_VALUE_TYPE_BOOL_INTEL
                                                                                , PERFORMANCE_VALUE_TYPE_STRING_INTEL
                                                                                , ..
                                                                                )
                                                     , QueryPoolCreateInfoINTEL
                                                     , INTEL_PERFORMANCE_QUERY_SPEC_VERSION
                                                     , pattern INTEL_PERFORMANCE_QUERY_SPEC_VERSION
                                                     , INTEL_PERFORMANCE_QUERY_EXTENSION_NAME
                                                     , pattern INTEL_PERFORMANCE_QUERY_EXTENSION_NAME
                                                     , PerformanceConfigurationINTEL(..)
                                                     ) where

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.ByteString (packCString)
import Data.ByteString (useAsCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.Trans.Cont (runContT)
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.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import Data.Word (Word32)
import Data.Word (Word64)
import Text.Read.Lex (Lexeme(Ident))
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkAcquirePerformanceConfigurationINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetPerformanceMarkerINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetPerformanceOverrideINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkCmdSetPerformanceStreamMarkerINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkGetPerformanceParameterINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkInitializePerformanceApiINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkQueueSetPerformanceConfigurationINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkReleasePerformanceConfigurationINTEL))
import Vulkan.Dynamic (DeviceCmds(pVkUninitializePerformanceApiINTEL))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Extensions.Handles (PerformanceConfigurationINTEL)
import Vulkan.Extensions.Handles (PerformanceConfigurationINTEL(..))
import Vulkan.Core10.Handles (Queue)
import Vulkan.Core10.Handles (Queue(..))
import Vulkan.Core10.Handles (Queue_T)
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.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.Handles (PerformanceConfigurationINTEL(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkInitializePerformanceApiINTEL
  :: FunPtr (Ptr Device_T -> Ptr InitializePerformanceApiInfoINTEL -> IO Result) -> Ptr Device_T -> Ptr InitializePerformanceApiInfoINTEL -> IO Result

-- | vkInitializePerformanceApiINTEL - Initialize a device for performance
-- queries
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'InitializePerformanceApiInfoINTEL'
initializePerformanceApiINTEL :: forall io
                               . (MonadIO io)
                              => -- | @device@ is the logical device used for the queries.
                                 --
                                 -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                 Device
                              -> -- | @pInitializeInfo@ is a pointer to a 'InitializePerformanceApiInfoINTEL'
                                 -- structure specifying initialization parameters.
                                 --
                                 -- @pInitializeInfo@ /must/ be a valid pointer to a valid
                                 -- 'InitializePerformanceApiInfoINTEL' structure
                                 ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
                              -> io ()
initializePerformanceApiINTEL :: Device
-> ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
-> io ()
initializePerformanceApiINTEL device :: Device
device initializeInfo :: "initializeInfo" ::: InitializePerformanceApiInfoINTEL
initializeInfo = 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 vkInitializePerformanceApiINTELPtr :: FunPtr
  (Ptr Device_T
   -> ("pInitializeInfo"
       ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
   -> IO Result)
vkInitializePerformanceApiINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pInitializeInfo"
          ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
      -> IO Result)
pVkInitializePerformanceApiINTEL (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
   -> ("pInitializeInfo"
       ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
   -> IO Result)
vkInitializePerformanceApiINTELPtr FunPtr
  (Ptr Device_T
   -> ("pInitializeInfo"
       ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pInitializeInfo"
          ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pInitializeInfo"
       ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
   -> 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 vkInitializePerformanceApiINTEL is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkInitializePerformanceApiINTEL' :: Ptr Device_T
-> ("pInitializeInfo"
    ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> IO Result
vkInitializePerformanceApiINTEL' = FunPtr
  (Ptr Device_T
   -> ("pInitializeInfo"
       ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
   -> IO Result)
-> Ptr Device_T
-> ("pInitializeInfo"
    ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> IO Result
mkVkInitializePerformanceApiINTEL FunPtr
  (Ptr Device_T
   -> ("pInitializeInfo"
       ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
   -> IO Result)
vkInitializePerformanceApiINTELPtr
  "pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
pInitializeInfo <- ((("pInitializeInfo"
   ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pInitializeInfo"
      ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInitializeInfo"
    ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pInitializeInfo"
       ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)))
-> ((("pInitializeInfo"
      ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pInitializeInfo"
      ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
forall a b. (a -> b) -> a -> b
$ ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
-> (("pInitializeInfo"
     ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("initializeInfo" ::: InitializePerformanceApiInfoINTEL
initializeInfo)
  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
-> ("pInitializeInfo"
    ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> IO Result
vkInitializePerformanceApiINTEL' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
pInitializeInfo
  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" mkVkUninitializePerformanceApiINTEL
  :: FunPtr (Ptr Device_T -> IO ()) -> Ptr Device_T -> IO ()

-- | vkUninitializePerformanceApiINTEL - Uninitialize a device for
-- performance queries
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device'
uninitializePerformanceApiINTEL :: forall io
                                 . (MonadIO io)
                                => -- | @device@ is the logical device used for the queries.
                                   --
                                   -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                   Device
                                -> io ()
uninitializePerformanceApiINTEL :: Device -> io ()
uninitializePerformanceApiINTEL device :: Device
device = 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 vkUninitializePerformanceApiINTELPtr :: FunPtr (Ptr Device_T -> IO ())
vkUninitializePerformanceApiINTELPtr = DeviceCmds -> FunPtr (Ptr Device_T -> IO ())
pVkUninitializePerformanceApiINTEL (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> IO ())
vkUninitializePerformanceApiINTELPtr FunPtr (Ptr Device_T -> IO ())
-> FunPtr (Ptr Device_T -> IO ()) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_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 vkUninitializePerformanceApiINTEL is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkUninitializePerformanceApiINTEL' :: Ptr Device_T -> IO ()
vkUninitializePerformanceApiINTEL' = FunPtr (Ptr Device_T -> IO ()) -> Ptr Device_T -> IO ()
mkVkUninitializePerformanceApiINTEL FunPtr (Ptr Device_T -> IO ())
vkUninitializePerformanceApiINTELPtr
  Ptr Device_T -> IO ()
vkUninitializePerformanceApiINTEL' (Device -> Ptr Device_T
deviceHandle (Device
device))
  () -> 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" mkVkCmdSetPerformanceMarkerINTEL
  :: FunPtr (Ptr CommandBuffer_T -> Ptr PerformanceMarkerInfoINTEL -> IO Result) -> Ptr CommandBuffer_T -> Ptr PerformanceMarkerInfoINTEL -> IO Result

-- | vkCmdSetPerformanceMarkerINTEL - Markers
--
-- = Parameters
--
-- The last marker set onto a command buffer before the end of a query will
-- be part of the query result.
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pMarkerInfo@ /must/ be a valid pointer to a valid
--     'PerformanceMarkerInfoINTEL' 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, compute, or transfer
--     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                                                                                                               |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Transfer                                                                                                              |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'PerformanceMarkerInfoINTEL'
cmdSetPerformanceMarkerINTEL :: forall io
                              . (MonadIO io)
                             => -- No documentation found for Nested "vkCmdSetPerformanceMarkerINTEL" "commandBuffer"
                                CommandBuffer
                             -> -- No documentation found for Nested "vkCmdSetPerformanceMarkerINTEL" "pMarkerInfo"
                                PerformanceMarkerInfoINTEL
                             -> io ()
cmdSetPerformanceMarkerINTEL :: CommandBuffer -> PerformanceMarkerInfoINTEL -> io ()
cmdSetPerformanceMarkerINTEL commandBuffer :: CommandBuffer
commandBuffer markerInfo :: PerformanceMarkerInfoINTEL
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 vkCmdSetPerformanceMarkerINTELPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
vkCmdSetPerformanceMarkerINTELPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
pVkCmdSetPerformanceMarkerINTEL (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 PerformanceMarkerInfoINTEL) -> IO Result)
vkCmdSetPerformanceMarkerINTELPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> 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 vkCmdSetPerformanceMarkerINTEL is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetPerformanceMarkerINTEL' :: Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result
vkCmdSetPerformanceMarkerINTEL' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
-> Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> IO Result
mkVkCmdSetPerformanceMarkerINTEL FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result)
vkCmdSetPerformanceMarkerINTELPtr
  "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
pMarkerInfo <- ((("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO ())
 -> IO ())
-> ContT () IO ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO ())
  -> IO ())
 -> ContT () IO ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL))
-> ((("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO ())
    -> IO ())
-> ContT () IO ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
forall a b. (a -> b) -> a -> b
$ PerformanceMarkerInfoINTEL
-> (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PerformanceMarkerInfoINTEL
markerInfo)
  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 CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO Result
vkCmdSetPerformanceMarkerINTEL' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
pMarkerInfo
  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" mkVkCmdSetPerformanceStreamMarkerINTEL
  :: FunPtr (Ptr CommandBuffer_T -> Ptr PerformanceStreamMarkerInfoINTEL -> IO Result) -> Ptr CommandBuffer_T -> Ptr PerformanceStreamMarkerInfoINTEL -> IO Result

-- | vkCmdSetPerformanceStreamMarkerINTEL - Markers
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pMarkerInfo@ /must/ be a valid pointer to a valid
--     'PerformanceStreamMarkerInfoINTEL' 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, compute, or transfer
--     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                                                                                                               |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Transfer                                                                                                              |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'PerformanceStreamMarkerInfoINTEL'
cmdSetPerformanceStreamMarkerINTEL :: forall io
                                    . (MonadIO io)
                                   => -- No documentation found for Nested "vkCmdSetPerformanceStreamMarkerINTEL" "commandBuffer"
                                      CommandBuffer
                                   -> -- No documentation found for Nested "vkCmdSetPerformanceStreamMarkerINTEL" "pMarkerInfo"
                                      PerformanceStreamMarkerInfoINTEL
                                   -> io ()
cmdSetPerformanceStreamMarkerINTEL :: CommandBuffer -> PerformanceStreamMarkerInfoINTEL -> io ()
cmdSetPerformanceStreamMarkerINTEL commandBuffer :: CommandBuffer
commandBuffer markerInfo :: PerformanceStreamMarkerInfoINTEL
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 vkCmdSetPerformanceStreamMarkerINTELPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceStreamMarkerINTELPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
      -> IO Result)
pVkCmdSetPerformanceStreamMarkerINTEL (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 PerformanceStreamMarkerInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceStreamMarkerINTELPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> IO Result)
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> 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 vkCmdSetPerformanceStreamMarkerINTEL is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetPerformanceStreamMarkerINTEL' :: Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> IO Result
vkCmdSetPerformanceStreamMarkerINTEL' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> IO Result)
-> Ptr CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> IO Result
mkVkCmdSetPerformanceStreamMarkerINTEL FunPtr
  (Ptr CommandBuffer_T
   -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceStreamMarkerINTELPtr
  "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
pMarkerInfo <- ((("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
  -> IO ())
 -> IO ())
-> ContT
     () IO ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
   -> IO ())
  -> IO ())
 -> ContT
      () IO ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL))
-> ((("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
     -> IO ())
    -> IO ())
-> ContT
     () IO ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
forall a b. (a -> b) -> a -> b
$ PerformanceStreamMarkerInfoINTEL
-> (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PerformanceStreamMarkerInfoINTEL
markerInfo)
  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 CommandBuffer_T
-> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> IO Result
vkCmdSetPerformanceStreamMarkerINTEL' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
pMarkerInfo
  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" mkVkCmdSetPerformanceOverrideINTEL
  :: FunPtr (Ptr CommandBuffer_T -> Ptr PerformanceOverrideInfoINTEL -> IO Result) -> Ptr CommandBuffer_T -> Ptr PerformanceOverrideInfoINTEL -> IO Result

-- | vkCmdSetPerformanceOverrideINTEL - Performance override settings
--
-- == Valid Usage
--
-- -   @pOverrideInfo@ /must/ not be used with a
--     'PerformanceOverrideTypeINTEL' that is not reported available by
--     'getPerformanceParameterINTEL'
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pOverrideInfo@ /must/ be a valid pointer to a valid
--     'PerformanceOverrideInfoINTEL' 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, compute, or transfer
--     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                                                                                                               |                                                                                                                                     |
-- |                                                                                                                            |                                                                                                                        | Transfer                                                                                                              |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'PerformanceOverrideInfoINTEL'
cmdSetPerformanceOverrideINTEL :: forall io
                                . (MonadIO io)
                               => -- | @commandBuffer@ is the command buffer where the override takes place.
                                  CommandBuffer
                               -> -- | @pOverrideInfo@ is a pointer to a 'PerformanceOverrideInfoINTEL'
                                  -- structure selecting the parameter to override.
                                  PerformanceOverrideInfoINTEL
                               -> io ()
cmdSetPerformanceOverrideINTEL :: CommandBuffer -> PerformanceOverrideInfoINTEL -> io ()
cmdSetPerformanceOverrideINTEL commandBuffer :: CommandBuffer
commandBuffer overrideInfo :: PerformanceOverrideInfoINTEL
overrideInfo = 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 vkCmdSetPerformanceOverrideINTELPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceOverrideINTELPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
      -> IO Result)
pVkCmdSetPerformanceOverrideINTEL (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
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceOverrideINTELPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> IO Result)
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> 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 vkCmdSetPerformanceOverrideINTEL is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdSetPerformanceOverrideINTEL' :: Ptr CommandBuffer_T
-> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO Result
vkCmdSetPerformanceOverrideINTEL' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> IO Result)
-> Ptr CommandBuffer_T
-> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO Result
mkVkCmdSetPerformanceOverrideINTEL FunPtr
  (Ptr CommandBuffer_T
   -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
   -> IO Result)
vkCmdSetPerformanceOverrideINTELPtr
  "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
pOverrideInfo <- ((("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO ())
 -> IO ())
-> ContT
     () IO ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO ())
  -> IO ())
 -> ContT
      () IO ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL))
-> ((("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
     -> IO ())
    -> IO ())
-> ContT
     () IO ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
forall a b. (a -> b) -> a -> b
$ PerformanceOverrideInfoINTEL
-> (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PerformanceOverrideInfoINTEL
overrideInfo)
  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 CommandBuffer_T
-> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO Result
vkCmdSetPerformanceOverrideINTEL' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
pOverrideInfo
  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" mkVkAcquirePerformanceConfigurationINTEL
  :: FunPtr (Ptr Device_T -> Ptr PerformanceConfigurationAcquireInfoINTEL -> Ptr PerformanceConfigurationINTEL -> IO Result) -> Ptr Device_T -> Ptr PerformanceConfigurationAcquireInfoINTEL -> Ptr PerformanceConfigurationINTEL -> IO Result

-- | vkAcquirePerformanceConfigurationINTEL - Acquire the performance query
-- capability
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device',
-- 'PerformanceConfigurationAcquireInfoINTEL',
-- 'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL'
acquirePerformanceConfigurationINTEL :: forall io
                                      . (MonadIO io)
                                     => -- | @device@ is the logical device that the performance query commands will
                                        -- be submitted to.
                                        --
                                        -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                        Device
                                     -> -- | @pAcquireInfo@ is a pointer to a
                                        -- 'PerformanceConfigurationAcquireInfoINTEL' structure, specifying the
                                        -- performance configuration to acquire.
                                        --
                                        -- @pAcquireInfo@ /must/ be a valid pointer to a valid
                                        -- 'PerformanceConfigurationAcquireInfoINTEL' structure
                                        PerformanceConfigurationAcquireInfoINTEL
                                     -> io (PerformanceConfigurationINTEL)
acquirePerformanceConfigurationINTEL :: Device
-> PerformanceConfigurationAcquireInfoINTEL
-> io PerformanceConfigurationINTEL
acquirePerformanceConfigurationINTEL device :: Device
device acquireInfo :: PerformanceConfigurationAcquireInfoINTEL
acquireInfo = IO PerformanceConfigurationINTEL
-> io PerformanceConfigurationINTEL
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PerformanceConfigurationINTEL
 -> io PerformanceConfigurationINTEL)
-> (ContT
      PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL
    -> IO PerformanceConfigurationINTEL)
-> ContT
     PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL
-> io PerformanceConfigurationINTEL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL
-> IO PerformanceConfigurationINTEL
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL
 -> io PerformanceConfigurationINTEL)
-> ContT
     PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL
-> io PerformanceConfigurationINTEL
forall a b. (a -> b) -> a -> b
$ do
  let vkAcquirePerformanceConfigurationINTELPtr :: FunPtr
  (Ptr Device_T
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO Result)
vkAcquirePerformanceConfigurationINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pAcquireInfo"
          ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
      -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
      -> IO Result)
pVkAcquirePerformanceConfigurationINTEL (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT PerformanceConfigurationINTEL IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PerformanceConfigurationINTEL IO ())
-> IO () -> ContT PerformanceConfigurationINTEL IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO Result)
vkAcquirePerformanceConfigurationINTELPtr FunPtr
  (Ptr Device_T
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pAcquireInfo"
          ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
      -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> 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 vkAcquirePerformanceConfigurationINTEL is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkAcquirePerformanceConfigurationINTEL' :: Ptr Device_T
-> ("pAcquireInfo"
    ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
-> IO Result
vkAcquirePerformanceConfigurationINTEL' = FunPtr
  (Ptr Device_T
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO Result)
-> Ptr Device_T
-> ("pAcquireInfo"
    ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
-> IO Result
mkVkAcquirePerformanceConfigurationINTEL FunPtr
  (Ptr Device_T
   -> ("pAcquireInfo"
       ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO Result)
vkAcquirePerformanceConfigurationINTELPtr
  "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
pAcquireInfo <- ((("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
  -> IO PerformanceConfigurationINTEL)
 -> IO PerformanceConfigurationINTEL)
-> ContT
     PerformanceConfigurationINTEL
     IO
     ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAcquireInfo"
    ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
   -> IO PerformanceConfigurationINTEL)
  -> IO PerformanceConfigurationINTEL)
 -> ContT
      PerformanceConfigurationINTEL
      IO
      ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL))
-> ((("pAcquireInfo"
      ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
     -> IO PerformanceConfigurationINTEL)
    -> IO PerformanceConfigurationINTEL)
-> ContT
     PerformanceConfigurationINTEL
     IO
     ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
forall a b. (a -> b) -> a -> b
$ PerformanceConfigurationAcquireInfoINTEL
-> (("pAcquireInfo"
     ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
    -> IO PerformanceConfigurationINTEL)
-> IO PerformanceConfigurationINTEL
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PerformanceConfigurationAcquireInfoINTEL
acquireInfo)
  "pConfiguration" ::: Ptr PerformanceConfigurationINTEL
pPConfiguration <- ((("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
  -> IO PerformanceConfigurationINTEL)
 -> IO PerformanceConfigurationINTEL)
-> ContT
     PerformanceConfigurationINTEL
     IO
     ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
   -> IO PerformanceConfigurationINTEL)
  -> IO PerformanceConfigurationINTEL)
 -> ContT
      PerformanceConfigurationINTEL
      IO
      ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL))
-> ((("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
     -> IO PerformanceConfigurationINTEL)
    -> IO PerformanceConfigurationINTEL)
-> ContT
     PerformanceConfigurationINTEL
     IO
     ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
forall a b. (a -> b) -> a -> b
$ IO ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
-> (("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
    -> IO ())
-> (("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
    -> IO PerformanceConfigurationINTEL)
-> IO PerformanceConfigurationINTEL
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
forall a. Int -> IO (Ptr a)
callocBytes @PerformanceConfigurationINTEL 8) ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT PerformanceConfigurationINTEL IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT PerformanceConfigurationINTEL IO Result)
-> IO Result -> ContT PerformanceConfigurationINTEL IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pAcquireInfo"
    ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
-> IO Result
vkAcquirePerformanceConfigurationINTEL' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
pAcquireInfo ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL
pPConfiguration)
  IO () -> ContT PerformanceConfigurationINTEL IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PerformanceConfigurationINTEL IO ())
-> IO () -> ContT PerformanceConfigurationINTEL 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))
  PerformanceConfigurationINTEL
pConfiguration <- IO PerformanceConfigurationINTEL
-> ContT
     PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO PerformanceConfigurationINTEL
 -> ContT
      PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL)
-> IO PerformanceConfigurationINTEL
-> ContT
     PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL
forall a b. (a -> b) -> a -> b
$ ("pConfiguration" ::: Ptr PerformanceConfigurationINTEL)
-> IO PerformanceConfigurationINTEL
forall a. Storable a => Ptr a -> IO a
peek @PerformanceConfigurationINTEL "pConfiguration" ::: Ptr PerformanceConfigurationINTEL
pPConfiguration
  PerformanceConfigurationINTEL
-> ContT
     PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PerformanceConfigurationINTEL
 -> ContT
      PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL)
-> PerformanceConfigurationINTEL
-> ContT
     PerformanceConfigurationINTEL IO PerformanceConfigurationINTEL
forall a b. (a -> b) -> a -> b
$ (PerformanceConfigurationINTEL
pConfiguration)


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

-- | vkReleasePerformanceConfigurationINTEL - Release a configuration to
-- capture performance data
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL'
releasePerformanceConfigurationINTEL :: forall io
                                      . (MonadIO io)
                                     => -- | @device@ is the device associated to the configuration object to
                                        -- release.
                                        --
                                        -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                        Device
                                     -> -- | @configuration@ is the configuration object to release.
                                        --
                                        -- @configuration@ /must/ not be released before all command buffers
                                        -- submitted while the configuration was set are in
                                        -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle pending state>
                                        --
                                        -- @configuration@ /must/ be a valid
                                        -- 'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL' handle
                                        --
                                        -- @configuration@ /must/ have been created, allocated, or retrieved from
                                        -- @device@
                                        PerformanceConfigurationINTEL
                                     -> io ()
releasePerformanceConfigurationINTEL :: Device -> PerformanceConfigurationINTEL -> io ()
releasePerformanceConfigurationINTEL device :: Device
device configuration :: PerformanceConfigurationINTEL
configuration = 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 vkReleasePerformanceConfigurationINTELPtr :: FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
vkReleasePerformanceConfigurationINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
pVkReleasePerformanceConfigurationINTEL (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
vkReleasePerformanceConfigurationINTELPtr FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
-> FunPtr
     (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> 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 vkReleasePerformanceConfigurationINTEL is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkReleasePerformanceConfigurationINTEL' :: Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result
vkReleasePerformanceConfigurationINTEL' = FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
-> Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result
mkVkReleasePerformanceConfigurationINTEL FunPtr (Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result)
vkReleasePerformanceConfigurationINTELPtr
  Result
r <- Ptr Device_T -> PerformanceConfigurationINTEL -> IO Result
vkReleasePerformanceConfigurationINTEL' (Device -> Ptr Device_T
deviceHandle (Device
device)) (PerformanceConfigurationINTEL
configuration)
  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" mkVkQueueSetPerformanceConfigurationINTEL
  :: FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result) -> Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result

-- | vkQueueSetPerformanceConfigurationINTEL - Set a performance query
--
-- == Valid Usage (Implicit)
--
-- -   @queue@ /must/ be a valid 'Vulkan.Core10.Handles.Queue' handle
--
-- -   @configuration@ /must/ be a valid
--     'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL' handle
--
-- -   Both of @configuration@, and @queue@ /must/ have been created,
--     allocated, or retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- == 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> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | -                                                                                                                          | -                                                                                                                      | Any                                                                                                                   | -                                                                                                                                   |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.PerformanceConfigurationINTEL',
-- 'Vulkan.Core10.Handles.Queue'
queueSetPerformanceConfigurationINTEL :: forall io
                                       . (MonadIO io)
                                      => -- | @queue@ is the queue on which the configuration will be used.
                                         Queue
                                      -> -- | @configuration@ is the configuration to use.
                                         PerformanceConfigurationINTEL
                                      -> io ()
queueSetPerformanceConfigurationINTEL :: Queue -> PerformanceConfigurationINTEL -> io ()
queueSetPerformanceConfigurationINTEL queue :: Queue
queue configuration :: PerformanceConfigurationINTEL
configuration = 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 vkQueueSetPerformanceConfigurationINTELPtr :: FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
vkQueueSetPerformanceConfigurationINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
pVkQueueSetPerformanceConfigurationINTEL (Queue -> DeviceCmds
deviceCmds (Queue
queue :: Queue))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
vkQueueSetPerformanceConfigurationINTELPtr FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
-> FunPtr
     (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> 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 vkQueueSetPerformanceConfigurationINTEL is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkQueueSetPerformanceConfigurationINTEL' :: Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result
vkQueueSetPerformanceConfigurationINTEL' = FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
-> Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result
mkVkQueueSetPerformanceConfigurationINTEL FunPtr (Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result)
vkQueueSetPerformanceConfigurationINTELPtr
  Result
r <- Ptr Queue_T -> PerformanceConfigurationINTEL -> IO Result
vkQueueSetPerformanceConfigurationINTEL' (Queue -> Ptr Queue_T
queueHandle (Queue
queue)) (PerformanceConfigurationINTEL
configuration)
  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" mkVkGetPerformanceParameterINTEL
  :: FunPtr (Ptr Device_T -> PerformanceParameterTypeINTEL -> Ptr PerformanceValueINTEL -> IO Result) -> Ptr Device_T -> PerformanceParameterTypeINTEL -> Ptr PerformanceValueINTEL -> IO Result

-- | vkGetPerformanceParameterINTEL - Query performance capabilities of the
-- device
--
-- == 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_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'PerformanceParameterTypeINTEL',
-- 'PerformanceValueINTEL'
getPerformanceParameterINTEL :: forall io
                              . (MonadIO io)
                             => -- | @device@ is the logical device to query.
                                --
                                -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                Device
                             -> -- | @parameter@ is the parameter to query.
                                --
                                -- @parameter@ /must/ be a valid 'PerformanceParameterTypeINTEL' value
                                PerformanceParameterTypeINTEL
                             -> io (PerformanceValueINTEL)
getPerformanceParameterINTEL :: Device -> PerformanceParameterTypeINTEL -> io PerformanceValueINTEL
getPerformanceParameterINTEL device :: Device
device parameter :: PerformanceParameterTypeINTEL
parameter = IO PerformanceValueINTEL -> io PerformanceValueINTEL
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PerformanceValueINTEL -> io PerformanceValueINTEL)
-> (ContT PerformanceValueINTEL IO PerformanceValueINTEL
    -> IO PerformanceValueINTEL)
-> ContT PerformanceValueINTEL IO PerformanceValueINTEL
-> io PerformanceValueINTEL
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT PerformanceValueINTEL IO PerformanceValueINTEL
-> IO PerformanceValueINTEL
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT PerformanceValueINTEL IO PerformanceValueINTEL
 -> io PerformanceValueINTEL)
-> ContT PerformanceValueINTEL IO PerformanceValueINTEL
-> io PerformanceValueINTEL
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPerformanceParameterINTELPtr :: FunPtr
  (Ptr Device_T
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> IO Result)
vkGetPerformanceParameterINTELPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> PerformanceParameterTypeINTEL
      -> ("pValue" ::: Ptr PerformanceValueINTEL)
      -> IO Result)
pVkGetPerformanceParameterINTEL (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT PerformanceValueINTEL IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PerformanceValueINTEL IO ())
-> IO () -> ContT PerformanceValueINTEL IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> IO Result)
vkGetPerformanceParameterINTELPtr FunPtr
  (Ptr Device_T
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> PerformanceParameterTypeINTEL
      -> ("pValue" ::: Ptr PerformanceValueINTEL)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> 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 vkGetPerformanceParameterINTEL is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPerformanceParameterINTEL' :: Ptr Device_T
-> PerformanceParameterTypeINTEL
-> ("pValue" ::: Ptr PerformanceValueINTEL)
-> IO Result
vkGetPerformanceParameterINTEL' = FunPtr
  (Ptr Device_T
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> IO Result)
-> Ptr Device_T
-> PerformanceParameterTypeINTEL
-> ("pValue" ::: Ptr PerformanceValueINTEL)
-> IO Result
mkVkGetPerformanceParameterINTEL FunPtr
  (Ptr Device_T
   -> PerformanceParameterTypeINTEL
   -> ("pValue" ::: Ptr PerformanceValueINTEL)
   -> IO Result)
vkGetPerformanceParameterINTELPtr
  "pValue" ::: Ptr PerformanceValueINTEL
pPValue <- ((("pValue" ::: Ptr PerformanceValueINTEL)
  -> IO PerformanceValueINTEL)
 -> IO PerformanceValueINTEL)
-> ContT
     PerformanceValueINTEL IO ("pValue" ::: Ptr PerformanceValueINTEL)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct PerformanceValueINTEL =>
(("pValue" ::: Ptr PerformanceValueINTEL) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @PerformanceValueINTEL)
  Result
r <- IO Result -> ContT PerformanceValueINTEL IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT PerformanceValueINTEL IO Result)
-> IO Result -> ContT PerformanceValueINTEL IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> PerformanceParameterTypeINTEL
-> ("pValue" ::: Ptr PerformanceValueINTEL)
-> IO Result
vkGetPerformanceParameterINTEL' (Device -> Ptr Device_T
deviceHandle (Device
device)) (PerformanceParameterTypeINTEL
parameter) ("pValue" ::: Ptr PerformanceValueINTEL
pPValue)
  IO () -> ContT PerformanceValueINTEL IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PerformanceValueINTEL IO ())
-> IO () -> ContT PerformanceValueINTEL 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))
  PerformanceValueINTEL
pValue <- IO PerformanceValueINTEL
-> ContT PerformanceValueINTEL IO PerformanceValueINTEL
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO PerformanceValueINTEL
 -> ContT PerformanceValueINTEL IO PerformanceValueINTEL)
-> IO PerformanceValueINTEL
-> ContT PerformanceValueINTEL IO PerformanceValueINTEL
forall a b. (a -> b) -> a -> b
$ ("pValue" ::: Ptr PerformanceValueINTEL)
-> IO PerformanceValueINTEL
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PerformanceValueINTEL "pValue" ::: Ptr PerformanceValueINTEL
pPValue
  PerformanceValueINTEL
-> ContT PerformanceValueINTEL IO PerformanceValueINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PerformanceValueINTEL
 -> ContT PerformanceValueINTEL IO PerformanceValueINTEL)
-> PerformanceValueINTEL
-> ContT PerformanceValueINTEL IO PerformanceValueINTEL
forall a b. (a -> b) -> a -> b
$ (PerformanceValueINTEL
pValue)


-- No documentation found for TopLevel "VK_STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL"
pattern $bSTRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL :: StructureType
$mSTRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL :: forall r. StructureType -> (Void# -> r) -> (Void# -> r) -> r
STRUCTURE_TYPE_QUERY_POOL_CREATE_INFO_INTEL = STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL


-- | VkPerformanceValueINTEL - Container for value and types of parameters
-- that can be queried
--
-- == Valid Usage (Implicit)
--
-- -   @type@ /must/ be a valid 'PerformanceValueTypeINTEL' value
--
-- -   If @type@ is 'PERFORMANCE_VALUE_TYPE_STRING_INTEL', the
--     @valueString@ member of @data@ /must/ be a null-terminated UTF-8
--     string
--
-- = See Also
--
-- 'PerformanceValueDataINTEL', 'PerformanceValueTypeINTEL',
-- 'getPerformanceParameterINTEL'
data PerformanceValueINTEL = PerformanceValueINTEL
  { -- | @type@ is a 'PerformanceValueTypeINTEL' value specifying the type of the
    -- returned data.
    PerformanceValueINTEL -> PerformanceValueTypeINTEL
type' :: PerformanceValueTypeINTEL
  , -- | @data@ is a 'PerformanceValueDataINTEL' union specifying the value of
    -- the returned data.
    PerformanceValueINTEL -> PerformanceValueDataINTEL
data' :: PerformanceValueDataINTEL
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceValueINTEL)
#endif
deriving instance Show PerformanceValueINTEL

instance ToCStruct PerformanceValueINTEL where
  withCStruct :: PerformanceValueINTEL
-> (("pValue" ::: Ptr PerformanceValueINTEL) -> IO b) -> IO b
withCStruct x :: PerformanceValueINTEL
x f :: ("pValue" ::: Ptr PerformanceValueINTEL) -> IO b
f = Int
-> Int
-> (("pValue" ::: Ptr PerformanceValueINTEL) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 8 ((("pValue" ::: Ptr PerformanceValueINTEL) -> IO b) -> IO b)
-> (("pValue" ::: Ptr PerformanceValueINTEL) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pValue" ::: Ptr PerformanceValueINTEL
p -> ("pValue" ::: Ptr PerformanceValueINTEL)
-> PerformanceValueINTEL -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pValue" ::: Ptr PerformanceValueINTEL
p PerformanceValueINTEL
x (("pValue" ::: Ptr PerformanceValueINTEL) -> IO b
f "pValue" ::: Ptr PerformanceValueINTEL
p)
  pokeCStruct :: ("pValue" ::: Ptr PerformanceValueINTEL)
-> PerformanceValueINTEL -> IO b -> IO b
pokeCStruct p :: "pValue" ::: Ptr PerformanceValueINTEL
p PerformanceValueINTEL{..} 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 PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pValue" ::: Ptr PerformanceValueINTEL
p ("pValue" ::: Ptr PerformanceValueINTEL)
-> Int -> Ptr PerformanceValueTypeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr PerformanceValueTypeINTEL)) (PerformanceValueTypeINTEL
type')
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PerformanceValueDataINTEL
-> PerformanceValueDataINTEL -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pValue" ::: Ptr PerformanceValueINTEL
p ("pValue" ::: Ptr PerformanceValueINTEL)
-> Int -> Ptr PerformanceValueDataINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PerformanceValueDataINTEL)) (PerformanceValueDataINTEL
data') (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    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 = 16
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pValue" ::: Ptr PerformanceValueINTEL) -> IO b -> IO b
pokeZeroCStruct p :: "pValue" ::: Ptr PerformanceValueINTEL
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 PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pValue" ::: Ptr PerformanceValueINTEL
p ("pValue" ::: Ptr PerformanceValueINTEL)
-> Int -> Ptr PerformanceValueTypeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr PerformanceValueTypeINTEL)) (PerformanceValueTypeINTEL
forall a. Zero a => a
zero)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PerformanceValueDataINTEL
-> PerformanceValueDataINTEL -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pValue" ::: Ptr PerformanceValueINTEL
p ("pValue" ::: Ptr PerformanceValueINTEL)
-> Int -> Ptr PerformanceValueDataINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PerformanceValueDataINTEL)) (PerformanceValueDataINTEL
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    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 PerformanceValueINTEL where
  peekCStruct :: ("pValue" ::: Ptr PerformanceValueINTEL)
-> IO PerformanceValueINTEL
peekCStruct p :: "pValue" ::: Ptr PerformanceValueINTEL
p = do
    PerformanceValueTypeINTEL
type' <- Ptr PerformanceValueTypeINTEL -> IO PerformanceValueTypeINTEL
forall a. Storable a => Ptr a -> IO a
peek @PerformanceValueTypeINTEL (("pValue" ::: Ptr PerformanceValueINTEL
p ("pValue" ::: Ptr PerformanceValueINTEL)
-> Int -> Ptr PerformanceValueTypeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr PerformanceValueTypeINTEL))
    PerformanceValueDataINTEL
data' <- PerformanceValueTypeINTEL
-> Ptr PerformanceValueDataINTEL -> IO PerformanceValueDataINTEL
peekPerformanceValueDataINTEL PerformanceValueTypeINTEL
type' (("pValue" ::: Ptr PerformanceValueINTEL
p ("pValue" ::: Ptr PerformanceValueINTEL)
-> Int -> Ptr PerformanceValueDataINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PerformanceValueDataINTEL))
    PerformanceValueINTEL -> IO PerformanceValueINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PerformanceValueINTEL -> IO PerformanceValueINTEL)
-> PerformanceValueINTEL -> IO PerformanceValueINTEL
forall a b. (a -> b) -> a -> b
$ PerformanceValueTypeINTEL
-> PerformanceValueDataINTEL -> PerformanceValueINTEL
PerformanceValueINTEL
             PerformanceValueTypeINTEL
type' PerformanceValueDataINTEL
data'

instance Zero PerformanceValueINTEL where
  zero :: PerformanceValueINTEL
zero = PerformanceValueTypeINTEL
-> PerformanceValueDataINTEL -> PerformanceValueINTEL
PerformanceValueINTEL
           PerformanceValueTypeINTEL
forall a. Zero a => a
zero
           PerformanceValueDataINTEL
forall a. Zero a => a
zero


-- | VkInitializePerformanceApiInfoINTEL - Structure specifying parameters of
-- initialize of the device
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'initializePerformanceApiINTEL'
data InitializePerformanceApiInfoINTEL = InitializePerformanceApiInfoINTEL
  { -- | @pUserData@ is a pointer for application data.
    ("initializeInfo" ::: InitializePerformanceApiInfoINTEL) -> Ptr ()
userData :: Ptr () }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (InitializePerformanceApiInfoINTEL)
#endif
deriving instance Show InitializePerformanceApiInfoINTEL

instance ToCStruct InitializePerformanceApiInfoINTEL where
  withCStruct :: ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
-> (("pInitializeInfo"
     ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
    -> IO b)
-> IO b
withCStruct x :: "initializeInfo" ::: InitializePerformanceApiInfoINTEL
x f :: ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> IO b
f = Int
-> Int
-> (("pInitializeInfo"
     ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pInitializeInfo"
   ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
  -> IO b)
 -> IO b)
-> (("pInitializeInfo"
     ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p -> ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p "initializeInfo" ::: InitializePerformanceApiInfoINTEL
x (("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> IO b
f "pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p)
  pokeCStruct :: ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
-> IO b
-> IO b
pokeCStruct p :: "pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p InitializePerformanceApiInfoINTEL{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr ()))) (Ptr ()
userData)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> IO b -> IO b
pokeZeroCStruct p :: "pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_INITIALIZE_PERFORMANCE_API_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr ()))) (Ptr ()
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct InitializePerformanceApiInfoINTEL where
  peekCStruct :: ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> IO ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
peekCStruct p :: "pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p = do
    Ptr ()
pUserData <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) (("pInitializeInfo"
::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
p ("pInitializeInfo"
 ::: Ptr ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr ())))
    ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
-> IO ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
 -> IO ("initializeInfo" ::: InitializePerformanceApiInfoINTEL))
-> ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
-> IO ("initializeInfo" ::: InitializePerformanceApiInfoINTEL)
forall a b. (a -> b) -> a -> b
$ Ptr () -> "initializeInfo" ::: InitializePerformanceApiInfoINTEL
InitializePerformanceApiInfoINTEL
             Ptr ()
pUserData

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

instance Zero InitializePerformanceApiInfoINTEL where
  zero :: "initializeInfo" ::: InitializePerformanceApiInfoINTEL
zero = Ptr () -> "initializeInfo" ::: InitializePerformanceApiInfoINTEL
InitializePerformanceApiInfoINTEL
           Ptr ()
forall a. Zero a => a
zero


-- | VkQueryPoolPerformanceQueryCreateInfoINTEL - Structure specifying
-- parameters to create a pool of performance queries
--
-- = Members
--
-- To create a pool for Intel performance queries, set
-- 'Vulkan.Core10.Query.QueryPoolCreateInfo'::@queryType@ to
-- 'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_INTEL' and
-- add a 'QueryPoolPerformanceQueryCreateInfoINTEL' structure to the
-- @pNext@ chain of the 'Vulkan.Core10.Query.QueryPoolCreateInfo'
-- structure.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'QueryPoolSamplingModeINTEL',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data QueryPoolPerformanceQueryCreateInfoINTEL = QueryPoolPerformanceQueryCreateInfoINTEL
  { -- | @performanceCountersSampling@ describe how performance queries should be
    -- captured.
    --
    -- @performanceCountersSampling@ /must/ be a valid
    -- 'QueryPoolSamplingModeINTEL' value
    QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolSamplingModeINTEL
performanceCountersSampling :: QueryPoolSamplingModeINTEL }
  deriving (Typeable, QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
(QueryPoolPerformanceQueryCreateInfoINTEL
 -> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool)
-> (QueryPoolPerformanceQueryCreateInfoINTEL
    -> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool)
-> Eq QueryPoolPerformanceQueryCreateInfoINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
$c/= :: QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
== :: QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
$c== :: QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (QueryPoolPerformanceQueryCreateInfoINTEL)
#endif
deriving instance Show QueryPoolPerformanceQueryCreateInfoINTEL

instance ToCStruct QueryPoolPerformanceQueryCreateInfoINTEL where
  withCStruct :: QueryPoolPerformanceQueryCreateInfoINTEL
-> (Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b) -> IO b
withCStruct x :: QueryPoolPerformanceQueryCreateInfoINTEL
x f :: Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b
f = Int
-> Int
-> (Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b) -> IO b)
-> (Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p -> Ptr QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p QueryPoolPerformanceQueryCreateInfoINTEL
x (Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b
f Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p)
  pokeCStruct :: Ptr QueryPoolPerformanceQueryCreateInfoINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL -> IO b -> IO b
pokeCStruct p :: Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p QueryPoolPerformanceQueryCreateInfoINTEL{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p Ptr QueryPoolPerformanceQueryCreateInfoINTEL
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p Ptr QueryPoolPerformanceQueryCreateInfoINTEL
-> Int -> Ptr QueryPoolSamplingModeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr QueryPoolSamplingModeINTEL)) (QueryPoolSamplingModeINTEL
performanceCountersSampling)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> IO b -> IO b
pokeZeroCStruct p :: Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p Ptr QueryPoolPerformanceQueryCreateInfoINTEL
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUERY_POOL_PERFORMANCE_QUERY_CREATE_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p Ptr QueryPoolPerformanceQueryCreateInfoINTEL -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p Ptr QueryPoolPerformanceQueryCreateInfoINTEL
-> Int -> Ptr QueryPoolSamplingModeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr QueryPoolSamplingModeINTEL)) (QueryPoolSamplingModeINTEL
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct QueryPoolPerformanceQueryCreateInfoINTEL where
  peekCStruct :: Ptr QueryPoolPerformanceQueryCreateInfoINTEL
-> IO QueryPoolPerformanceQueryCreateInfoINTEL
peekCStruct p :: Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p = do
    QueryPoolSamplingModeINTEL
performanceCountersSampling <- Ptr QueryPoolSamplingModeINTEL -> IO QueryPoolSamplingModeINTEL
forall a. Storable a => Ptr a -> IO a
peek @QueryPoolSamplingModeINTEL ((Ptr QueryPoolPerformanceQueryCreateInfoINTEL
p Ptr QueryPoolPerformanceQueryCreateInfoINTEL
-> Int -> Ptr QueryPoolSamplingModeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr QueryPoolSamplingModeINTEL))
    QueryPoolPerformanceQueryCreateInfoINTEL
-> IO QueryPoolPerformanceQueryCreateInfoINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (QueryPoolPerformanceQueryCreateInfoINTEL
 -> IO QueryPoolPerformanceQueryCreateInfoINTEL)
-> QueryPoolPerformanceQueryCreateInfoINTEL
-> IO QueryPoolPerformanceQueryCreateInfoINTEL
forall a b. (a -> b) -> a -> b
$ QueryPoolSamplingModeINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL
QueryPoolPerformanceQueryCreateInfoINTEL
             QueryPoolSamplingModeINTEL
performanceCountersSampling

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

instance Zero QueryPoolPerformanceQueryCreateInfoINTEL where
  zero :: QueryPoolPerformanceQueryCreateInfoINTEL
zero = QueryPoolSamplingModeINTEL
-> QueryPoolPerformanceQueryCreateInfoINTEL
QueryPoolPerformanceQueryCreateInfoINTEL
           QueryPoolSamplingModeINTEL
forall a. Zero a => a
zero


-- | VkPerformanceMarkerInfoINTEL - Structure specifying performance markers
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdSetPerformanceMarkerINTEL'
data PerformanceMarkerInfoINTEL = PerformanceMarkerInfoINTEL
  { -- | @marker@ is the marker value that will be recorded into the opaque query
    -- results.
    PerformanceMarkerInfoINTEL -> Word64
marker :: Word64 }
  deriving (Typeable, PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
(PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool)
-> (PerformanceMarkerInfoINTEL
    -> PerformanceMarkerInfoINTEL -> Bool)
-> Eq PerformanceMarkerInfoINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
$c/= :: PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
== :: PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
$c== :: PerformanceMarkerInfoINTEL -> PerformanceMarkerInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceMarkerInfoINTEL)
#endif
deriving instance Show PerformanceMarkerInfoINTEL

instance ToCStruct PerformanceMarkerInfoINTEL where
  withCStruct :: PerformanceMarkerInfoINTEL
-> (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b)
-> IO b
withCStruct x :: PerformanceMarkerInfoINTEL
x f :: ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b
f = Int
-> Int
-> (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b)
 -> IO b)
-> (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p -> ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> PerformanceMarkerInfoINTEL -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p PerformanceMarkerInfoINTEL
x (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b
f "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p)
  pokeCStruct :: ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> PerformanceMarkerInfoINTEL -> IO b -> IO b
pokeCStruct p :: "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p PerformanceMarkerInfoINTEL{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word64)) (Word64
marker)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL) -> IO b -> IO b
pokeZeroCStruct p :: "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_MARKER_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PerformanceMarkerInfoINTEL where
  peekCStruct :: ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> IO PerformanceMarkerInfoINTEL
peekCStruct p :: "pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p = do
    Word64
marker <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceMarkerInfoINTEL)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word64))
    PerformanceMarkerInfoINTEL -> IO PerformanceMarkerInfoINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PerformanceMarkerInfoINTEL -> IO PerformanceMarkerInfoINTEL)
-> PerformanceMarkerInfoINTEL -> IO PerformanceMarkerInfoINTEL
forall a b. (a -> b) -> a -> b
$ Word64 -> PerformanceMarkerInfoINTEL
PerformanceMarkerInfoINTEL
             Word64
marker

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

instance Zero PerformanceMarkerInfoINTEL where
  zero :: PerformanceMarkerInfoINTEL
zero = Word64 -> PerformanceMarkerInfoINTEL
PerformanceMarkerInfoINTEL
           Word64
forall a. Zero a => a
zero


-- | VkPerformanceStreamMarkerInfoINTEL - Structure specifying stream
-- performance markers
--
-- == Valid Usage
--
-- -   The value written by the application into @marker@ /must/ only used
--     the valid bits as reported by 'getPerformanceParameterINTEL' with
--     the 'PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL'
--
-- -   @pNext@ /must/ be @NULL@
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdSetPerformanceStreamMarkerINTEL'
data PerformanceStreamMarkerInfoINTEL = PerformanceStreamMarkerInfoINTEL
  { -- | @marker@ is the marker value that will be recorded into the reports
    -- consumed by an external application.
    PerformanceStreamMarkerInfoINTEL -> Word32
marker :: Word32 }
  deriving (Typeable, PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
(PerformanceStreamMarkerInfoINTEL
 -> PerformanceStreamMarkerInfoINTEL -> Bool)
-> (PerformanceStreamMarkerInfoINTEL
    -> PerformanceStreamMarkerInfoINTEL -> Bool)
-> Eq PerformanceStreamMarkerInfoINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
$c/= :: PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
== :: PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
$c== :: PerformanceStreamMarkerInfoINTEL
-> PerformanceStreamMarkerInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceStreamMarkerInfoINTEL)
#endif
deriving instance Show PerformanceStreamMarkerInfoINTEL

instance ToCStruct PerformanceStreamMarkerInfoINTEL where
  withCStruct :: PerformanceStreamMarkerInfoINTEL
-> (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
    -> IO b)
-> IO b
withCStruct x :: PerformanceStreamMarkerInfoINTEL
x f :: ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL) -> IO b
f = Int
-> Int
-> (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL) -> IO b)
 -> IO b)
-> (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p -> ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> PerformanceStreamMarkerInfoINTEL -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p PerformanceStreamMarkerInfoINTEL
x (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL) -> IO b
f "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p)
  pokeCStruct :: ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> PerformanceStreamMarkerInfoINTEL -> IO b -> IO b
pokeCStruct p :: "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p PerformanceStreamMarkerInfoINTEL{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
marker)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> IO b -> IO b
pokeZeroCStruct p :: "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_STREAM_MARKER_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PerformanceStreamMarkerInfoINTEL where
  peekCStruct :: ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> IO PerformanceStreamMarkerInfoINTEL
peekCStruct p :: "pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p = do
    Word32
marker <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL
p ("pMarkerInfo" ::: Ptr PerformanceStreamMarkerInfoINTEL)
-> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    PerformanceStreamMarkerInfoINTEL
-> IO PerformanceStreamMarkerInfoINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PerformanceStreamMarkerInfoINTEL
 -> IO PerformanceStreamMarkerInfoINTEL)
-> PerformanceStreamMarkerInfoINTEL
-> IO PerformanceStreamMarkerInfoINTEL
forall a b. (a -> b) -> a -> b
$ Word32 -> PerformanceStreamMarkerInfoINTEL
PerformanceStreamMarkerInfoINTEL
             Word32
marker

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

instance Zero PerformanceStreamMarkerInfoINTEL where
  zero :: PerformanceStreamMarkerInfoINTEL
zero = Word32 -> PerformanceStreamMarkerInfoINTEL
PerformanceStreamMarkerInfoINTEL
           Word32
forall a. Zero a => a
zero


-- | VkPerformanceOverrideInfoINTEL - Performance override info
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'PerformanceOverrideTypeINTEL',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdSetPerformanceOverrideINTEL'
data PerformanceOverrideInfoINTEL = PerformanceOverrideInfoINTEL
  { -- | @type@ is the particular 'PerformanceOverrideTypeINTEL' to set.
    --
    -- @type@ /must/ be a valid 'PerformanceOverrideTypeINTEL' value
    PerformanceOverrideInfoINTEL -> PerformanceOverrideTypeINTEL
type' :: PerformanceOverrideTypeINTEL
  , -- | @enable@ defines whether the override is enabled.
    PerformanceOverrideInfoINTEL -> Bool
enable :: Bool
  , -- | @parameter@ is a potential required parameter for the override.
    PerformanceOverrideInfoINTEL -> Word64
parameter :: Word64
  }
  deriving (Typeable, PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
(PerformanceOverrideInfoINTEL
 -> PerformanceOverrideInfoINTEL -> Bool)
-> (PerformanceOverrideInfoINTEL
    -> PerformanceOverrideInfoINTEL -> Bool)
-> Eq PerformanceOverrideInfoINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
$c/= :: PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
== :: PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
$c== :: PerformanceOverrideInfoINTEL
-> PerformanceOverrideInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceOverrideInfoINTEL)
#endif
deriving instance Show PerformanceOverrideInfoINTEL

instance ToCStruct PerformanceOverrideInfoINTEL where
  withCStruct :: PerformanceOverrideInfoINTEL
-> (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO b)
-> IO b
withCStruct x :: PerformanceOverrideInfoINTEL
x f :: ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO b
f = Int
-> Int
-> (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO b)
 -> IO b)
-> (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p -> ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> PerformanceOverrideInfoINTEL -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p PerformanceOverrideInfoINTEL
x (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL) -> IO b
f "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p)
  pokeCStruct :: ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> PerformanceOverrideInfoINTEL -> IO b -> IO b
pokeCStruct p :: "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p PerformanceOverrideInfoINTEL{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr PerformanceOverrideTypeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PerformanceOverrideTypeINTEL)) (PerformanceOverrideTypeINTEL
type')
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
enable))
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64)) (Word64
parameter)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO b -> IO b
pokeZeroCStruct p :: "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_OVERRIDE_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr PerformanceOverrideTypeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PerformanceOverrideTypeINTEL)) (PerformanceOverrideTypeINTEL
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PerformanceOverrideInfoINTEL where
  peekCStruct :: ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> IO PerformanceOverrideInfoINTEL
peekCStruct p :: "pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p = do
    PerformanceOverrideTypeINTEL
type' <- Ptr PerformanceOverrideTypeINTEL -> IO PerformanceOverrideTypeINTEL
forall a. Storable a => Ptr a -> IO a
peek @PerformanceOverrideTypeINTEL (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr PerformanceOverrideTypeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PerformanceOverrideTypeINTEL))
    Bool32
enable <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Word64
parameter <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 (("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL
p ("pOverrideInfo" ::: Ptr PerformanceOverrideInfoINTEL)
-> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word64))
    PerformanceOverrideInfoINTEL -> IO PerformanceOverrideInfoINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PerformanceOverrideInfoINTEL -> IO PerformanceOverrideInfoINTEL)
-> PerformanceOverrideInfoINTEL -> IO PerformanceOverrideInfoINTEL
forall a b. (a -> b) -> a -> b
$ PerformanceOverrideTypeINTEL
-> Bool -> Word64 -> PerformanceOverrideInfoINTEL
PerformanceOverrideInfoINTEL
             PerformanceOverrideTypeINTEL
type' (Bool32 -> Bool
bool32ToBool Bool32
enable) Word64
parameter

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

instance Zero PerformanceOverrideInfoINTEL where
  zero :: PerformanceOverrideInfoINTEL
zero = PerformanceOverrideTypeINTEL
-> Bool -> Word64 -> PerformanceOverrideInfoINTEL
PerformanceOverrideInfoINTEL
           PerformanceOverrideTypeINTEL
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero


-- | VkPerformanceConfigurationAcquireInfoINTEL - Acquire a configuration to
-- capture performance data
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'PerformanceConfigurationTypeINTEL',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'acquirePerformanceConfigurationINTEL'
data PerformanceConfigurationAcquireInfoINTEL = PerformanceConfigurationAcquireInfoINTEL
  { -- | @type@ is one of the 'PerformanceConfigurationTypeINTEL' type of
    -- performance configuration that will be acquired.
    --
    -- @type@ /must/ be a valid 'PerformanceConfigurationTypeINTEL' value
    PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationTypeINTEL
type' :: PerformanceConfigurationTypeINTEL }
  deriving (Typeable, PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
(PerformanceConfigurationAcquireInfoINTEL
 -> PerformanceConfigurationAcquireInfoINTEL -> Bool)
-> (PerformanceConfigurationAcquireInfoINTEL
    -> PerformanceConfigurationAcquireInfoINTEL -> Bool)
-> Eq PerformanceConfigurationAcquireInfoINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
$c/= :: PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
== :: PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
$c== :: PerformanceConfigurationAcquireInfoINTEL
-> PerformanceConfigurationAcquireInfoINTEL -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PerformanceConfigurationAcquireInfoINTEL)
#endif
deriving instance Show PerformanceConfigurationAcquireInfoINTEL

instance ToCStruct PerformanceConfigurationAcquireInfoINTEL where
  withCStruct :: PerformanceConfigurationAcquireInfoINTEL
-> (("pAcquireInfo"
     ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
    -> IO b)
-> IO b
withCStruct x :: PerformanceConfigurationAcquireInfoINTEL
x f :: ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> IO b
f = Int
-> Int
-> (("pAcquireInfo"
     ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
  -> IO b)
 -> IO b)
-> (("pAcquireInfo"
     ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p -> ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> PerformanceConfigurationAcquireInfoINTEL -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p PerformanceConfigurationAcquireInfoINTEL
x (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> IO b
f "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p)
  pokeCStruct :: ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> PerformanceConfigurationAcquireInfoINTEL -> IO b -> IO b
pokeCStruct p :: "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p PerformanceConfigurationAcquireInfoINTEL{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> Int -> Ptr PerformanceConfigurationTypeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PerformanceConfigurationTypeINTEL)) (PerformanceConfigurationTypeINTEL
type')
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> IO b -> IO b
pokeZeroCStruct p :: "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PERFORMANCE_CONFIGURATION_ACQUIRE_INFO_INTEL)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> Int -> Ptr PerformanceConfigurationTypeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PerformanceConfigurationTypeINTEL)) (PerformanceConfigurationTypeINTEL
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PerformanceConfigurationAcquireInfoINTEL where
  peekCStruct :: ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> IO PerformanceConfigurationAcquireInfoINTEL
peekCStruct p :: "pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p = do
    PerformanceConfigurationTypeINTEL
type' <- Ptr PerformanceConfigurationTypeINTEL
-> IO PerformanceConfigurationTypeINTEL
forall a. Storable a => Ptr a -> IO a
peek @PerformanceConfigurationTypeINTEL (("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL
p ("pAcquireInfo" ::: Ptr PerformanceConfigurationAcquireInfoINTEL)
-> Int -> Ptr PerformanceConfigurationTypeINTEL
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PerformanceConfigurationTypeINTEL))
    PerformanceConfigurationAcquireInfoINTEL
-> IO PerformanceConfigurationAcquireInfoINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PerformanceConfigurationAcquireInfoINTEL
 -> IO PerformanceConfigurationAcquireInfoINTEL)
-> PerformanceConfigurationAcquireInfoINTEL
-> IO PerformanceConfigurationAcquireInfoINTEL
forall a b. (a -> b) -> a -> b
$ PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationAcquireInfoINTEL
PerformanceConfigurationAcquireInfoINTEL
             PerformanceConfigurationTypeINTEL
type'

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

instance Zero PerformanceConfigurationAcquireInfoINTEL where
  zero :: PerformanceConfigurationAcquireInfoINTEL
zero = PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationAcquireInfoINTEL
PerformanceConfigurationAcquireInfoINTEL
           PerformanceConfigurationTypeINTEL
forall a. Zero a => a
zero


data PerformanceValueDataINTEL
  = Value32 Word32
  | Value64 Word64
  | ValueFloat Float
  | ValueBool Bool
  | ValueString ByteString
  deriving (Int -> PerformanceValueDataINTEL -> ShowS
[PerformanceValueDataINTEL] -> ShowS
PerformanceValueDataINTEL -> String
(Int -> PerformanceValueDataINTEL -> ShowS)
-> (PerformanceValueDataINTEL -> String)
-> ([PerformanceValueDataINTEL] -> ShowS)
-> Show PerformanceValueDataINTEL
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PerformanceValueDataINTEL] -> ShowS
$cshowList :: [PerformanceValueDataINTEL] -> ShowS
show :: PerformanceValueDataINTEL -> String
$cshow :: PerformanceValueDataINTEL -> String
showsPrec :: Int -> PerformanceValueDataINTEL -> ShowS
$cshowsPrec :: Int -> PerformanceValueDataINTEL -> ShowS
Show)

instance ToCStruct PerformanceValueDataINTEL where
  withCStruct :: PerformanceValueDataINTEL
-> (Ptr PerformanceValueDataINTEL -> IO b) -> IO b
withCStruct x :: PerformanceValueDataINTEL
x f :: Ptr PerformanceValueDataINTEL -> IO b
f = Int -> Int -> (Ptr PerformanceValueDataINTEL -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 8 ((Ptr PerformanceValueDataINTEL -> IO b) -> IO b)
-> (Ptr PerformanceValueDataINTEL -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PerformanceValueDataINTEL
p -> Ptr PerformanceValueDataINTEL
-> PerformanceValueDataINTEL -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PerformanceValueDataINTEL
p PerformanceValueDataINTEL
x (Ptr PerformanceValueDataINTEL -> IO b
f Ptr PerformanceValueDataINTEL
p)
  pokeCStruct :: Ptr PerformanceValueDataINTEL -> PerformanceValueDataINTEL -> IO a -> IO a
  pokeCStruct :: Ptr PerformanceValueDataINTEL
-> PerformanceValueDataINTEL -> IO a -> IO a
pokeCStruct p :: Ptr PerformanceValueDataINTEL
p = (((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const) (((() -> IO a) -> IO a) -> IO a -> IO a)
-> (PerformanceValueDataINTEL -> (() -> IO a) -> IO a)
-> PerformanceValueDataINTEL
-> IO a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT a IO () -> (() -> IO a) -> IO a
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (ContT a IO () -> (() -> IO a) -> IO a)
-> (PerformanceValueDataINTEL -> ContT a IO ())
-> PerformanceValueDataINTEL
-> (() -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  \case
    Value32 v :: Word32
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PerformanceValueDataINTEL -> Ptr Word32
forall a b. Ptr a -> Ptr b
castPtr @_ @Word32 Ptr PerformanceValueDataINTEL
p) (Word32
v)
    Value64 v :: Word64
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PerformanceValueDataINTEL -> Ptr Word64
forall a b. Ptr a -> Ptr b
castPtr @_ @Word64 Ptr PerformanceValueDataINTEL
p) (Word64
v)
    ValueFloat v :: Float
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PerformanceValueDataINTEL -> Ptr CFloat
forall a b. Ptr a -> Ptr b
castPtr @_ @CFloat Ptr PerformanceValueDataINTEL
p) (Float -> CFloat
CFloat (Float
v))
    ValueBool v :: Bool
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PerformanceValueDataINTEL -> Ptr Bool32
forall a b. Ptr a -> Ptr b
castPtr @_ @Bool32 Ptr PerformanceValueDataINTEL
p) (Bool -> Bool32
boolToBool32 (Bool
v))
    ValueString v :: ByteString
v -> do
      CString
valueString <- ((CString -> IO a) -> IO a) -> ContT a IO CString
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((CString -> IO a) -> IO a) -> ContT a IO CString)
-> ((CString -> IO a) -> IO a) -> ContT a IO CString
forall a b. (a -> b) -> a -> b
$ ByteString -> (CString -> IO a) -> IO a
forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString (ByteString
v)
      IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PerformanceValueDataINTEL -> Ptr CString
forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr CChar) Ptr PerformanceValueDataINTEL
p) CString
valueString
  pokeZeroCStruct :: Ptr PerformanceValueDataINTEL -> IO b -> IO b
  pokeZeroCStruct :: Ptr PerformanceValueDataINTEL -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 8

instance Zero PerformanceValueDataINTEL where
  zero :: PerformanceValueDataINTEL
zero = Word64 -> PerformanceValueDataINTEL
Value64 Word64
forall a. Zero a => a
zero

peekPerformanceValueDataINTEL :: PerformanceValueTypeINTEL -> Ptr PerformanceValueDataINTEL -> IO PerformanceValueDataINTEL
peekPerformanceValueDataINTEL :: PerformanceValueTypeINTEL
-> Ptr PerformanceValueDataINTEL -> IO PerformanceValueDataINTEL
peekPerformanceValueDataINTEL tag :: PerformanceValueTypeINTEL
tag p :: Ptr PerformanceValueDataINTEL
p = case PerformanceValueTypeINTEL
tag of
  PERFORMANCE_VALUE_TYPE_UINT32_INTEL -> Word32 -> PerformanceValueDataINTEL
Value32 (Word32 -> PerformanceValueDataINTEL)
-> IO Word32 -> IO PerformanceValueDataINTEL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 (Ptr PerformanceValueDataINTEL -> Ptr Word32
forall a b. Ptr a -> Ptr b
castPtr @_ @Word32 Ptr PerformanceValueDataINTEL
p))
  PERFORMANCE_VALUE_TYPE_UINT64_INTEL -> Word64 -> PerformanceValueDataINTEL
Value64 (Word64 -> PerformanceValueDataINTEL)
-> IO Word64 -> IO PerformanceValueDataINTEL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 (Ptr PerformanceValueDataINTEL -> Ptr Word64
forall a b. Ptr a -> Ptr b
castPtr @_ @Word64 Ptr PerformanceValueDataINTEL
p))
  PERFORMANCE_VALUE_TYPE_FLOAT_INTEL -> Float -> PerformanceValueDataINTEL
ValueFloat (Float -> PerformanceValueDataINTEL)
-> IO Float -> IO PerformanceValueDataINTEL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
    CFloat
valueFloat <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat (Ptr PerformanceValueDataINTEL -> Ptr CFloat
forall a b. Ptr a -> Ptr b
castPtr @_ @CFloat Ptr PerformanceValueDataINTEL
p)
    Float -> IO Float
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Float -> IO Float) -> Float -> IO Float
forall a b. (a -> b) -> a -> b
$ (\(CFloat a :: Float
a) -> Float
a) CFloat
valueFloat)
  PERFORMANCE_VALUE_TYPE_BOOL_INTEL -> Bool -> PerformanceValueDataINTEL
ValueBool (Bool -> PerformanceValueDataINTEL)
-> IO Bool -> IO PerformanceValueDataINTEL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (do
    Bool32
valueBool <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 (Ptr PerformanceValueDataINTEL -> Ptr Bool32
forall a b. Ptr a -> Ptr b
castPtr @_ @Bool32 Ptr PerformanceValueDataINTEL
p)
    Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Bool32 -> Bool
bool32ToBool Bool32
valueBool)
  PERFORMANCE_VALUE_TYPE_STRING_INTEL -> ByteString -> PerformanceValueDataINTEL
ValueString (ByteString -> PerformanceValueDataINTEL)
-> IO ByteString -> IO PerformanceValueDataINTEL
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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 (Ptr PerformanceValueDataINTEL -> Ptr CString
forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr CChar) Ptr PerformanceValueDataINTEL
p))


-- | VkPerformanceConfigurationTypeINTEL - Type of performance configuration
--
-- = See Also
--
-- 'PerformanceConfigurationAcquireInfoINTEL'
newtype PerformanceConfigurationTypeINTEL = PerformanceConfigurationTypeINTEL Int32
  deriving newtype (PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
(PerformanceConfigurationTypeINTEL
 -> PerformanceConfigurationTypeINTEL -> Bool)
-> (PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL -> Bool)
-> Eq PerformanceConfigurationTypeINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c/= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
== :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c== :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
Eq, Eq PerformanceConfigurationTypeINTEL
Eq PerformanceConfigurationTypeINTEL =>
(PerformanceConfigurationTypeINTEL
 -> PerformanceConfigurationTypeINTEL -> Ordering)
-> (PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL -> Bool)
-> (PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL -> Bool)
-> (PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL -> Bool)
-> (PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL -> Bool)
-> (PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL)
-> (PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL)
-> Ord PerformanceConfigurationTypeINTEL
PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Ordering
PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
$cmin :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
max :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
$cmax :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL
>= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c>= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
> :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c> :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
<= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c<= :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
< :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
$c< :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Bool
compare :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Ordering
$ccompare :: PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> Ordering
$cp1Ord :: Eq PerformanceConfigurationTypeINTEL
Ord, Ptr b -> Int -> IO PerformanceConfigurationTypeINTEL
Ptr b -> Int -> PerformanceConfigurationTypeINTEL -> IO ()
Ptr PerformanceConfigurationTypeINTEL
-> IO PerformanceConfigurationTypeINTEL
Ptr PerformanceConfigurationTypeINTEL
-> Int -> IO PerformanceConfigurationTypeINTEL
Ptr PerformanceConfigurationTypeINTEL
-> Int -> PerformanceConfigurationTypeINTEL -> IO ()
Ptr PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> IO ()
PerformanceConfigurationTypeINTEL -> Int
(PerformanceConfigurationTypeINTEL -> Int)
-> (PerformanceConfigurationTypeINTEL -> Int)
-> (Ptr PerformanceConfigurationTypeINTEL
    -> Int -> IO PerformanceConfigurationTypeINTEL)
-> (Ptr PerformanceConfigurationTypeINTEL
    -> Int -> PerformanceConfigurationTypeINTEL -> IO ())
-> (forall b. Ptr b -> Int -> IO PerformanceConfigurationTypeINTEL)
-> (forall b.
    Ptr b -> Int -> PerformanceConfigurationTypeINTEL -> IO ())
-> (Ptr PerformanceConfigurationTypeINTEL
    -> IO PerformanceConfigurationTypeINTEL)
-> (Ptr PerformanceConfigurationTypeINTEL
    -> PerformanceConfigurationTypeINTEL -> IO ())
-> Storable PerformanceConfigurationTypeINTEL
forall b. Ptr b -> Int -> IO PerformanceConfigurationTypeINTEL
forall b.
Ptr b -> Int -> PerformanceConfigurationTypeINTEL -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> IO ()
$cpoke :: Ptr PerformanceConfigurationTypeINTEL
-> PerformanceConfigurationTypeINTEL -> IO ()
peek :: Ptr PerformanceConfigurationTypeINTEL
-> IO PerformanceConfigurationTypeINTEL
$cpeek :: Ptr PerformanceConfigurationTypeINTEL
-> IO PerformanceConfigurationTypeINTEL
pokeByteOff :: Ptr b -> Int -> PerformanceConfigurationTypeINTEL -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> PerformanceConfigurationTypeINTEL -> IO ()
peekByteOff :: Ptr b -> Int -> IO PerformanceConfigurationTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceConfigurationTypeINTEL
pokeElemOff :: Ptr PerformanceConfigurationTypeINTEL
-> Int -> PerformanceConfigurationTypeINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceConfigurationTypeINTEL
-> Int -> PerformanceConfigurationTypeINTEL -> IO ()
peekElemOff :: Ptr PerformanceConfigurationTypeINTEL
-> Int -> IO PerformanceConfigurationTypeINTEL
$cpeekElemOff :: Ptr PerformanceConfigurationTypeINTEL
-> Int -> IO PerformanceConfigurationTypeINTEL
alignment :: PerformanceConfigurationTypeINTEL -> Int
$calignment :: PerformanceConfigurationTypeINTEL -> Int
sizeOf :: PerformanceConfigurationTypeINTEL -> Int
$csizeOf :: PerformanceConfigurationTypeINTEL -> Int
Storable, PerformanceConfigurationTypeINTEL
PerformanceConfigurationTypeINTEL
-> Zero PerformanceConfigurationTypeINTEL
forall a. a -> Zero a
zero :: PerformanceConfigurationTypeINTEL
$czero :: PerformanceConfigurationTypeINTEL
Zero)

-- No documentation found for Nested "VkPerformanceConfigurationTypeINTEL" "VK_PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL"
pattern $bPERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL :: PerformanceConfigurationTypeINTEL
$mPERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL :: forall r.
PerformanceConfigurationTypeINTEL
-> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL = PerformanceConfigurationTypeINTEL 0
{-# complete PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL :: PerformanceConfigurationTypeINTEL #-}

instance Show PerformanceConfigurationTypeINTEL where
  showsPrec :: Int -> PerformanceConfigurationTypeINTEL -> ShowS
showsPrec p :: Int
p = \case
    PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL -> String -> ShowS
showString "PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL"
    PerformanceConfigurationTypeINTEL x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PerformanceConfigurationTypeINTEL " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read PerformanceConfigurationTypeINTEL where
  readPrec :: ReadPrec PerformanceConfigurationTypeINTEL
readPrec = ReadPrec PerformanceConfigurationTypeINTEL
-> ReadPrec PerformanceConfigurationTypeINTEL
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec PerformanceConfigurationTypeINTEL)]
-> ReadPrec PerformanceConfigurationTypeINTEL
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL", PerformanceConfigurationTypeINTEL
-> ReadPrec PerformanceConfigurationTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceConfigurationTypeINTEL
PERFORMANCE_CONFIGURATION_TYPE_COMMAND_QUEUE_METRICS_DISCOVERY_ACTIVATED_INTEL)]
                     ReadPrec PerformanceConfigurationTypeINTEL
-> ReadPrec PerformanceConfigurationTypeINTEL
-> ReadPrec PerformanceConfigurationTypeINTEL
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec PerformanceConfigurationTypeINTEL
-> ReadPrec PerformanceConfigurationTypeINTEL
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "PerformanceConfigurationTypeINTEL")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       PerformanceConfigurationTypeINTEL
-> ReadPrec PerformanceConfigurationTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> PerformanceConfigurationTypeINTEL
PerformanceConfigurationTypeINTEL Int32
v)))


-- | VkQueryPoolSamplingModeINTEL - Enum specifying how performance queries
-- should be captured
--
-- = See Also
--
-- 'QueryPoolPerformanceQueryCreateInfoINTEL'
newtype QueryPoolSamplingModeINTEL = QueryPoolSamplingModeINTEL Int32
  deriving newtype (QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
(QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool)
-> (QueryPoolSamplingModeINTEL
    -> QueryPoolSamplingModeINTEL -> Bool)
-> Eq QueryPoolSamplingModeINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c/= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
== :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c== :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
Eq, Eq QueryPoolSamplingModeINTEL
Eq QueryPoolSamplingModeINTEL =>
(QueryPoolSamplingModeINTEL
 -> QueryPoolSamplingModeINTEL -> Ordering)
-> (QueryPoolSamplingModeINTEL
    -> QueryPoolSamplingModeINTEL -> Bool)
-> (QueryPoolSamplingModeINTEL
    -> QueryPoolSamplingModeINTEL -> Bool)
-> (QueryPoolSamplingModeINTEL
    -> QueryPoolSamplingModeINTEL -> Bool)
-> (QueryPoolSamplingModeINTEL
    -> QueryPoolSamplingModeINTEL -> Bool)
-> (QueryPoolSamplingModeINTEL
    -> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL)
-> (QueryPoolSamplingModeINTEL
    -> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL)
-> Ord QueryPoolSamplingModeINTEL
QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> Ordering
QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
$cmin :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
max :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
$cmax :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL
>= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c>= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
> :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c> :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
<= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c<= :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
< :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
$c< :: QueryPoolSamplingModeINTEL -> QueryPoolSamplingModeINTEL -> Bool
compare :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> Ordering
$ccompare :: QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> Ordering
$cp1Ord :: Eq QueryPoolSamplingModeINTEL
Ord, Ptr b -> Int -> IO QueryPoolSamplingModeINTEL
Ptr b -> Int -> QueryPoolSamplingModeINTEL -> IO ()
Ptr QueryPoolSamplingModeINTEL -> IO QueryPoolSamplingModeINTEL
Ptr QueryPoolSamplingModeINTEL
-> Int -> IO QueryPoolSamplingModeINTEL
Ptr QueryPoolSamplingModeINTEL
-> Int -> QueryPoolSamplingModeINTEL -> IO ()
Ptr QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> IO ()
QueryPoolSamplingModeINTEL -> Int
(QueryPoolSamplingModeINTEL -> Int)
-> (QueryPoolSamplingModeINTEL -> Int)
-> (Ptr QueryPoolSamplingModeINTEL
    -> Int -> IO QueryPoolSamplingModeINTEL)
-> (Ptr QueryPoolSamplingModeINTEL
    -> Int -> QueryPoolSamplingModeINTEL -> IO ())
-> (forall b. Ptr b -> Int -> IO QueryPoolSamplingModeINTEL)
-> (forall b. Ptr b -> Int -> QueryPoolSamplingModeINTEL -> IO ())
-> (Ptr QueryPoolSamplingModeINTEL
    -> IO QueryPoolSamplingModeINTEL)
-> (Ptr QueryPoolSamplingModeINTEL
    -> QueryPoolSamplingModeINTEL -> IO ())
-> Storable QueryPoolSamplingModeINTEL
forall b. Ptr b -> Int -> IO QueryPoolSamplingModeINTEL
forall b. Ptr b -> Int -> QueryPoolSamplingModeINTEL -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> IO ()
$cpoke :: Ptr QueryPoolSamplingModeINTEL
-> QueryPoolSamplingModeINTEL -> IO ()
peek :: Ptr QueryPoolSamplingModeINTEL -> IO QueryPoolSamplingModeINTEL
$cpeek :: Ptr QueryPoolSamplingModeINTEL -> IO QueryPoolSamplingModeINTEL
pokeByteOff :: Ptr b -> Int -> QueryPoolSamplingModeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> QueryPoolSamplingModeINTEL -> IO ()
peekByteOff :: Ptr b -> Int -> IO QueryPoolSamplingModeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO QueryPoolSamplingModeINTEL
pokeElemOff :: Ptr QueryPoolSamplingModeINTEL
-> Int -> QueryPoolSamplingModeINTEL -> IO ()
$cpokeElemOff :: Ptr QueryPoolSamplingModeINTEL
-> Int -> QueryPoolSamplingModeINTEL -> IO ()
peekElemOff :: Ptr QueryPoolSamplingModeINTEL
-> Int -> IO QueryPoolSamplingModeINTEL
$cpeekElemOff :: Ptr QueryPoolSamplingModeINTEL
-> Int -> IO QueryPoolSamplingModeINTEL
alignment :: QueryPoolSamplingModeINTEL -> Int
$calignment :: QueryPoolSamplingModeINTEL -> Int
sizeOf :: QueryPoolSamplingModeINTEL -> Int
$csizeOf :: QueryPoolSamplingModeINTEL -> Int
Storable, QueryPoolSamplingModeINTEL
QueryPoolSamplingModeINTEL -> Zero QueryPoolSamplingModeINTEL
forall a. a -> Zero a
zero :: QueryPoolSamplingModeINTEL
$czero :: QueryPoolSamplingModeINTEL
Zero)

-- | 'QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL' is the default mode in which the
-- application calls 'Vulkan.Core10.CommandBufferBuilding.cmdBeginQuery'
-- and 'Vulkan.Core10.CommandBufferBuilding.cmdEndQuery' to record
-- performance data.
pattern $bQUERY_POOL_SAMPLING_MODE_MANUAL_INTEL :: QueryPoolSamplingModeINTEL
$mQUERY_POOL_SAMPLING_MODE_MANUAL_INTEL :: forall r.
QueryPoolSamplingModeINTEL -> (Void# -> r) -> (Void# -> r) -> r
QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL = QueryPoolSamplingModeINTEL 0
{-# complete QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL :: QueryPoolSamplingModeINTEL #-}

instance Show QueryPoolSamplingModeINTEL where
  showsPrec :: Int -> QueryPoolSamplingModeINTEL -> ShowS
showsPrec p :: Int
p = \case
    QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL -> String -> ShowS
showString "QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL"
    QueryPoolSamplingModeINTEL x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "QueryPoolSamplingModeINTEL " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read QueryPoolSamplingModeINTEL where
  readPrec :: ReadPrec QueryPoolSamplingModeINTEL
readPrec = ReadPrec QueryPoolSamplingModeINTEL
-> ReadPrec QueryPoolSamplingModeINTEL
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec QueryPoolSamplingModeINTEL)]
-> ReadPrec QueryPoolSamplingModeINTEL
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL", QueryPoolSamplingModeINTEL -> ReadPrec QueryPoolSamplingModeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure QueryPoolSamplingModeINTEL
QUERY_POOL_SAMPLING_MODE_MANUAL_INTEL)]
                     ReadPrec QueryPoolSamplingModeINTEL
-> ReadPrec QueryPoolSamplingModeINTEL
-> ReadPrec QueryPoolSamplingModeINTEL
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec QueryPoolSamplingModeINTEL
-> ReadPrec QueryPoolSamplingModeINTEL
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "QueryPoolSamplingModeINTEL")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       QueryPoolSamplingModeINTEL -> ReadPrec QueryPoolSamplingModeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> QueryPoolSamplingModeINTEL
QueryPoolSamplingModeINTEL Int32
v)))


-- | VkPerformanceOverrideTypeINTEL - Performance override type
--
-- = See Also
--
-- 'PerformanceOverrideInfoINTEL'
newtype PerformanceOverrideTypeINTEL = PerformanceOverrideTypeINTEL Int32
  deriving newtype (PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
(PerformanceOverrideTypeINTEL
 -> PerformanceOverrideTypeINTEL -> Bool)
-> (PerformanceOverrideTypeINTEL
    -> PerformanceOverrideTypeINTEL -> Bool)
-> Eq PerformanceOverrideTypeINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c/= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
== :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c== :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
Eq, Eq PerformanceOverrideTypeINTEL
Eq PerformanceOverrideTypeINTEL =>
(PerformanceOverrideTypeINTEL
 -> PerformanceOverrideTypeINTEL -> Ordering)
-> (PerformanceOverrideTypeINTEL
    -> PerformanceOverrideTypeINTEL -> Bool)
-> (PerformanceOverrideTypeINTEL
    -> PerformanceOverrideTypeINTEL -> Bool)
-> (PerformanceOverrideTypeINTEL
    -> PerformanceOverrideTypeINTEL -> Bool)
-> (PerformanceOverrideTypeINTEL
    -> PerformanceOverrideTypeINTEL -> Bool)
-> (PerformanceOverrideTypeINTEL
    -> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL)
-> (PerformanceOverrideTypeINTEL
    -> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL)
-> Ord PerformanceOverrideTypeINTEL
PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Ordering
PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
$cmin :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
max :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
$cmax :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> PerformanceOverrideTypeINTEL
>= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c>= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
> :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c> :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
<= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c<= :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
< :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
$c< :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Bool
compare :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Ordering
$ccompare :: PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> Ordering
$cp1Ord :: Eq PerformanceOverrideTypeINTEL
Ord, Ptr b -> Int -> IO PerformanceOverrideTypeINTEL
Ptr b -> Int -> PerformanceOverrideTypeINTEL -> IO ()
Ptr PerformanceOverrideTypeINTEL -> IO PerformanceOverrideTypeINTEL
Ptr PerformanceOverrideTypeINTEL
-> Int -> IO PerformanceOverrideTypeINTEL
Ptr PerformanceOverrideTypeINTEL
-> Int -> PerformanceOverrideTypeINTEL -> IO ()
Ptr PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> IO ()
PerformanceOverrideTypeINTEL -> Int
(PerformanceOverrideTypeINTEL -> Int)
-> (PerformanceOverrideTypeINTEL -> Int)
-> (Ptr PerformanceOverrideTypeINTEL
    -> Int -> IO PerformanceOverrideTypeINTEL)
-> (Ptr PerformanceOverrideTypeINTEL
    -> Int -> PerformanceOverrideTypeINTEL -> IO ())
-> (forall b. Ptr b -> Int -> IO PerformanceOverrideTypeINTEL)
-> (forall b.
    Ptr b -> Int -> PerformanceOverrideTypeINTEL -> IO ())
-> (Ptr PerformanceOverrideTypeINTEL
    -> IO PerformanceOverrideTypeINTEL)
-> (Ptr PerformanceOverrideTypeINTEL
    -> PerformanceOverrideTypeINTEL -> IO ())
-> Storable PerformanceOverrideTypeINTEL
forall b. Ptr b -> Int -> IO PerformanceOverrideTypeINTEL
forall b. Ptr b -> Int -> PerformanceOverrideTypeINTEL -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> IO ()
$cpoke :: Ptr PerformanceOverrideTypeINTEL
-> PerformanceOverrideTypeINTEL -> IO ()
peek :: Ptr PerformanceOverrideTypeINTEL -> IO PerformanceOverrideTypeINTEL
$cpeek :: Ptr PerformanceOverrideTypeINTEL -> IO PerformanceOverrideTypeINTEL
pokeByteOff :: Ptr b -> Int -> PerformanceOverrideTypeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PerformanceOverrideTypeINTEL -> IO ()
peekByteOff :: Ptr b -> Int -> IO PerformanceOverrideTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceOverrideTypeINTEL
pokeElemOff :: Ptr PerformanceOverrideTypeINTEL
-> Int -> PerformanceOverrideTypeINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceOverrideTypeINTEL
-> Int -> PerformanceOverrideTypeINTEL -> IO ()
peekElemOff :: Ptr PerformanceOverrideTypeINTEL
-> Int -> IO PerformanceOverrideTypeINTEL
$cpeekElemOff :: Ptr PerformanceOverrideTypeINTEL
-> Int -> IO PerformanceOverrideTypeINTEL
alignment :: PerformanceOverrideTypeINTEL -> Int
$calignment :: PerformanceOverrideTypeINTEL -> Int
sizeOf :: PerformanceOverrideTypeINTEL -> Int
$csizeOf :: PerformanceOverrideTypeINTEL -> Int
Storable, PerformanceOverrideTypeINTEL
PerformanceOverrideTypeINTEL -> Zero PerformanceOverrideTypeINTEL
forall a. a -> Zero a
zero :: PerformanceOverrideTypeINTEL
$czero :: PerformanceOverrideTypeINTEL
Zero)

-- | 'PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL' turns all rendering
-- operations into noop.
pattern $bPERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL :: PerformanceOverrideTypeINTEL
$mPERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL :: forall r.
PerformanceOverrideTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL = PerformanceOverrideTypeINTEL 0
-- | 'PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL' stalls the stream of
-- commands until all previously emitted commands have completed and all
-- caches been flushed and invalidated.
pattern $bPERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL :: PerformanceOverrideTypeINTEL
$mPERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL :: forall r.
PerformanceOverrideTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL = PerformanceOverrideTypeINTEL 1
{-# complete PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL,
             PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL :: PerformanceOverrideTypeINTEL #-}

instance Show PerformanceOverrideTypeINTEL where
  showsPrec :: Int -> PerformanceOverrideTypeINTEL -> ShowS
showsPrec p :: Int
p = \case
    PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL -> String -> ShowS
showString "PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL"
    PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL -> String -> ShowS
showString "PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL"
    PerformanceOverrideTypeINTEL x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PerformanceOverrideTypeINTEL " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read PerformanceOverrideTypeINTEL where
  readPrec :: ReadPrec PerformanceOverrideTypeINTEL
readPrec = ReadPrec PerformanceOverrideTypeINTEL
-> ReadPrec PerformanceOverrideTypeINTEL
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec PerformanceOverrideTypeINTEL)]
-> ReadPrec PerformanceOverrideTypeINTEL
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL", PerformanceOverrideTypeINTEL
-> ReadPrec PerformanceOverrideTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceOverrideTypeINTEL
PERFORMANCE_OVERRIDE_TYPE_NULL_HARDWARE_INTEL)
                            , ("PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL", PerformanceOverrideTypeINTEL
-> ReadPrec PerformanceOverrideTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceOverrideTypeINTEL
PERFORMANCE_OVERRIDE_TYPE_FLUSH_GPU_CACHES_INTEL)]
                     ReadPrec PerformanceOverrideTypeINTEL
-> ReadPrec PerformanceOverrideTypeINTEL
-> ReadPrec PerformanceOverrideTypeINTEL
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec PerformanceOverrideTypeINTEL
-> ReadPrec PerformanceOverrideTypeINTEL
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "PerformanceOverrideTypeINTEL")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       PerformanceOverrideTypeINTEL
-> ReadPrec PerformanceOverrideTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> PerformanceOverrideTypeINTEL
PerformanceOverrideTypeINTEL Int32
v)))


-- | VkPerformanceParameterTypeINTEL - Parameters that can be queried
--
-- = See Also
--
-- 'getPerformanceParameterINTEL'
newtype PerformanceParameterTypeINTEL = PerformanceParameterTypeINTEL Int32
  deriving newtype (PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
(PerformanceParameterTypeINTEL
 -> PerformanceParameterTypeINTEL -> Bool)
-> (PerformanceParameterTypeINTEL
    -> PerformanceParameterTypeINTEL -> Bool)
-> Eq PerformanceParameterTypeINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c/= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
== :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c== :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
Eq, Eq PerformanceParameterTypeINTEL
Eq PerformanceParameterTypeINTEL =>
(PerformanceParameterTypeINTEL
 -> PerformanceParameterTypeINTEL -> Ordering)
-> (PerformanceParameterTypeINTEL
    -> PerformanceParameterTypeINTEL -> Bool)
-> (PerformanceParameterTypeINTEL
    -> PerformanceParameterTypeINTEL -> Bool)
-> (PerformanceParameterTypeINTEL
    -> PerformanceParameterTypeINTEL -> Bool)
-> (PerformanceParameterTypeINTEL
    -> PerformanceParameterTypeINTEL -> Bool)
-> (PerformanceParameterTypeINTEL
    -> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL)
-> (PerformanceParameterTypeINTEL
    -> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL)
-> Ord PerformanceParameterTypeINTEL
PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Ordering
PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
$cmin :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
max :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
$cmax :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> PerformanceParameterTypeINTEL
>= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c>= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
> :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c> :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
<= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c<= :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
< :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
$c< :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Bool
compare :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Ordering
$ccompare :: PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> Ordering
$cp1Ord :: Eq PerformanceParameterTypeINTEL
Ord, Ptr b -> Int -> IO PerformanceParameterTypeINTEL
Ptr b -> Int -> PerformanceParameterTypeINTEL -> IO ()
Ptr PerformanceParameterTypeINTEL
-> IO PerformanceParameterTypeINTEL
Ptr PerformanceParameterTypeINTEL
-> Int -> IO PerformanceParameterTypeINTEL
Ptr PerformanceParameterTypeINTEL
-> Int -> PerformanceParameterTypeINTEL -> IO ()
Ptr PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> IO ()
PerformanceParameterTypeINTEL -> Int
(PerformanceParameterTypeINTEL -> Int)
-> (PerformanceParameterTypeINTEL -> Int)
-> (Ptr PerformanceParameterTypeINTEL
    -> Int -> IO PerformanceParameterTypeINTEL)
-> (Ptr PerformanceParameterTypeINTEL
    -> Int -> PerformanceParameterTypeINTEL -> IO ())
-> (forall b. Ptr b -> Int -> IO PerformanceParameterTypeINTEL)
-> (forall b.
    Ptr b -> Int -> PerformanceParameterTypeINTEL -> IO ())
-> (Ptr PerformanceParameterTypeINTEL
    -> IO PerformanceParameterTypeINTEL)
-> (Ptr PerformanceParameterTypeINTEL
    -> PerformanceParameterTypeINTEL -> IO ())
-> Storable PerformanceParameterTypeINTEL
forall b. Ptr b -> Int -> IO PerformanceParameterTypeINTEL
forall b. Ptr b -> Int -> PerformanceParameterTypeINTEL -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> IO ()
$cpoke :: Ptr PerformanceParameterTypeINTEL
-> PerformanceParameterTypeINTEL -> IO ()
peek :: Ptr PerformanceParameterTypeINTEL
-> IO PerformanceParameterTypeINTEL
$cpeek :: Ptr PerformanceParameterTypeINTEL
-> IO PerformanceParameterTypeINTEL
pokeByteOff :: Ptr b -> Int -> PerformanceParameterTypeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PerformanceParameterTypeINTEL -> IO ()
peekByteOff :: Ptr b -> Int -> IO PerformanceParameterTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceParameterTypeINTEL
pokeElemOff :: Ptr PerformanceParameterTypeINTEL
-> Int -> PerformanceParameterTypeINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceParameterTypeINTEL
-> Int -> PerformanceParameterTypeINTEL -> IO ()
peekElemOff :: Ptr PerformanceParameterTypeINTEL
-> Int -> IO PerformanceParameterTypeINTEL
$cpeekElemOff :: Ptr PerformanceParameterTypeINTEL
-> Int -> IO PerformanceParameterTypeINTEL
alignment :: PerformanceParameterTypeINTEL -> Int
$calignment :: PerformanceParameterTypeINTEL -> Int
sizeOf :: PerformanceParameterTypeINTEL -> Int
$csizeOf :: PerformanceParameterTypeINTEL -> Int
Storable, PerformanceParameterTypeINTEL
PerformanceParameterTypeINTEL -> Zero PerformanceParameterTypeINTEL
forall a. a -> Zero a
zero :: PerformanceParameterTypeINTEL
$czero :: PerformanceParameterTypeINTEL
Zero)

-- | 'PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL' has a boolean
-- result which tells whether hardware counters can be captured.
pattern $bPERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL :: PerformanceParameterTypeINTEL
$mPERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL :: forall r.
PerformanceParameterTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL = PerformanceParameterTypeINTEL 0
-- | 'PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL' has a 32
-- bits integer result which tells how many bits can be written into the
-- 'PerformanceValueINTEL' value.
pattern $bPERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL :: PerformanceParameterTypeINTEL
$mPERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL :: forall r.
PerformanceParameterTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL = PerformanceParameterTypeINTEL 1
{-# complete PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL,
             PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL :: PerformanceParameterTypeINTEL #-}

instance Show PerformanceParameterTypeINTEL where
  showsPrec :: Int -> PerformanceParameterTypeINTEL -> ShowS
showsPrec p :: Int
p = \case
    PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL -> String -> ShowS
showString "PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL"
    PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL -> String -> ShowS
showString "PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL"
    PerformanceParameterTypeINTEL x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PerformanceParameterTypeINTEL " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read PerformanceParameterTypeINTEL where
  readPrec :: ReadPrec PerformanceParameterTypeINTEL
readPrec = ReadPrec PerformanceParameterTypeINTEL
-> ReadPrec PerformanceParameterTypeINTEL
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec PerformanceParameterTypeINTEL)]
-> ReadPrec PerformanceParameterTypeINTEL
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL", PerformanceParameterTypeINTEL
-> ReadPrec PerformanceParameterTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceParameterTypeINTEL
PERFORMANCE_PARAMETER_TYPE_HW_COUNTERS_SUPPORTED_INTEL)
                            , ("PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL", PerformanceParameterTypeINTEL
-> ReadPrec PerformanceParameterTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceParameterTypeINTEL
PERFORMANCE_PARAMETER_TYPE_STREAM_MARKER_VALID_BITS_INTEL)]
                     ReadPrec PerformanceParameterTypeINTEL
-> ReadPrec PerformanceParameterTypeINTEL
-> ReadPrec PerformanceParameterTypeINTEL
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec PerformanceParameterTypeINTEL
-> ReadPrec PerformanceParameterTypeINTEL
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "PerformanceParameterTypeINTEL")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       PerformanceParameterTypeINTEL
-> ReadPrec PerformanceParameterTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> PerformanceParameterTypeINTEL
PerformanceParameterTypeINTEL Int32
v)))


-- | VkPerformanceValueTypeINTEL - Type of the parameters that can be queried
--
-- = See Also
--
-- 'PerformanceValueINTEL'
newtype PerformanceValueTypeINTEL = PerformanceValueTypeINTEL Int32
  deriving newtype (PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
(PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool)
-> (PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool)
-> Eq PerformanceValueTypeINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c/= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
== :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c== :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
Eq, Eq PerformanceValueTypeINTEL
Eq PerformanceValueTypeINTEL =>
(PerformanceValueTypeINTEL
 -> PerformanceValueTypeINTEL -> Ordering)
-> (PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool)
-> (PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool)
-> (PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool)
-> (PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool)
-> (PerformanceValueTypeINTEL
    -> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL)
-> (PerformanceValueTypeINTEL
    -> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL)
-> Ord PerformanceValueTypeINTEL
PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Ordering
PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
$cmin :: PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
max :: PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
$cmax :: PerformanceValueTypeINTEL
-> PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL
>= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c>= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
> :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c> :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
<= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c<= :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
< :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
$c< :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Bool
compare :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Ordering
$ccompare :: PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> Ordering
$cp1Ord :: Eq PerformanceValueTypeINTEL
Ord, Ptr b -> Int -> IO PerformanceValueTypeINTEL
Ptr b -> Int -> PerformanceValueTypeINTEL -> IO ()
Ptr PerformanceValueTypeINTEL -> IO PerformanceValueTypeINTEL
Ptr PerformanceValueTypeINTEL
-> Int -> IO PerformanceValueTypeINTEL
Ptr PerformanceValueTypeINTEL
-> Int -> PerformanceValueTypeINTEL -> IO ()
Ptr PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> IO ()
PerformanceValueTypeINTEL -> Int
(PerformanceValueTypeINTEL -> Int)
-> (PerformanceValueTypeINTEL -> Int)
-> (Ptr PerformanceValueTypeINTEL
    -> Int -> IO PerformanceValueTypeINTEL)
-> (Ptr PerformanceValueTypeINTEL
    -> Int -> PerformanceValueTypeINTEL -> IO ())
-> (forall b. Ptr b -> Int -> IO PerformanceValueTypeINTEL)
-> (forall b. Ptr b -> Int -> PerformanceValueTypeINTEL -> IO ())
-> (Ptr PerformanceValueTypeINTEL -> IO PerformanceValueTypeINTEL)
-> (Ptr PerformanceValueTypeINTEL
    -> PerformanceValueTypeINTEL -> IO ())
-> Storable PerformanceValueTypeINTEL
forall b. Ptr b -> Int -> IO PerformanceValueTypeINTEL
forall b. Ptr b -> Int -> PerformanceValueTypeINTEL -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> IO ()
$cpoke :: Ptr PerformanceValueTypeINTEL -> PerformanceValueTypeINTEL -> IO ()
peek :: Ptr PerformanceValueTypeINTEL -> IO PerformanceValueTypeINTEL
$cpeek :: Ptr PerformanceValueTypeINTEL -> IO PerformanceValueTypeINTEL
pokeByteOff :: Ptr b -> Int -> PerformanceValueTypeINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PerformanceValueTypeINTEL -> IO ()
peekByteOff :: Ptr b -> Int -> IO PerformanceValueTypeINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceValueTypeINTEL
pokeElemOff :: Ptr PerformanceValueTypeINTEL
-> Int -> PerformanceValueTypeINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceValueTypeINTEL
-> Int -> PerformanceValueTypeINTEL -> IO ()
peekElemOff :: Ptr PerformanceValueTypeINTEL
-> Int -> IO PerformanceValueTypeINTEL
$cpeekElemOff :: Ptr PerformanceValueTypeINTEL
-> Int -> IO PerformanceValueTypeINTEL
alignment :: PerformanceValueTypeINTEL -> Int
$calignment :: PerformanceValueTypeINTEL -> Int
sizeOf :: PerformanceValueTypeINTEL -> Int
$csizeOf :: PerformanceValueTypeINTEL -> Int
Storable, PerformanceValueTypeINTEL
PerformanceValueTypeINTEL -> Zero PerformanceValueTypeINTEL
forall a. a -> Zero a
zero :: PerformanceValueTypeINTEL
$czero :: PerformanceValueTypeINTEL
Zero)

-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_UINT32_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_UINT32_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_UINT32_INTEL :: forall r.
PerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_VALUE_TYPE_UINT32_INTEL = PerformanceValueTypeINTEL 0
-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_UINT64_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_UINT64_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_UINT64_INTEL :: forall r.
PerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_VALUE_TYPE_UINT64_INTEL = PerformanceValueTypeINTEL 1
-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_FLOAT_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_FLOAT_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_FLOAT_INTEL :: forall r.
PerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_VALUE_TYPE_FLOAT_INTEL = PerformanceValueTypeINTEL 2
-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_BOOL_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_BOOL_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_BOOL_INTEL :: forall r.
PerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_VALUE_TYPE_BOOL_INTEL = PerformanceValueTypeINTEL 3
-- No documentation found for Nested "VkPerformanceValueTypeINTEL" "VK_PERFORMANCE_VALUE_TYPE_STRING_INTEL"
pattern $bPERFORMANCE_VALUE_TYPE_STRING_INTEL :: PerformanceValueTypeINTEL
$mPERFORMANCE_VALUE_TYPE_STRING_INTEL :: forall r.
PerformanceValueTypeINTEL -> (Void# -> r) -> (Void# -> r) -> r
PERFORMANCE_VALUE_TYPE_STRING_INTEL = PerformanceValueTypeINTEL 4
{-# complete PERFORMANCE_VALUE_TYPE_UINT32_INTEL,
             PERFORMANCE_VALUE_TYPE_UINT64_INTEL,
             PERFORMANCE_VALUE_TYPE_FLOAT_INTEL,
             PERFORMANCE_VALUE_TYPE_BOOL_INTEL,
             PERFORMANCE_VALUE_TYPE_STRING_INTEL :: PerformanceValueTypeINTEL #-}

instance Show PerformanceValueTypeINTEL where
  showsPrec :: Int -> PerformanceValueTypeINTEL -> ShowS
showsPrec p :: Int
p = \case
    PERFORMANCE_VALUE_TYPE_UINT32_INTEL -> String -> ShowS
showString "PERFORMANCE_VALUE_TYPE_UINT32_INTEL"
    PERFORMANCE_VALUE_TYPE_UINT64_INTEL -> String -> ShowS
showString "PERFORMANCE_VALUE_TYPE_UINT64_INTEL"
    PERFORMANCE_VALUE_TYPE_FLOAT_INTEL -> String -> ShowS
showString "PERFORMANCE_VALUE_TYPE_FLOAT_INTEL"
    PERFORMANCE_VALUE_TYPE_BOOL_INTEL -> String -> ShowS
showString "PERFORMANCE_VALUE_TYPE_BOOL_INTEL"
    PERFORMANCE_VALUE_TYPE_STRING_INTEL -> String -> ShowS
showString "PERFORMANCE_VALUE_TYPE_STRING_INTEL"
    PerformanceValueTypeINTEL x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PerformanceValueTypeINTEL " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read PerformanceValueTypeINTEL where
  readPrec :: ReadPrec PerformanceValueTypeINTEL
readPrec = ReadPrec PerformanceValueTypeINTEL
-> ReadPrec PerformanceValueTypeINTEL
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec PerformanceValueTypeINTEL)]
-> ReadPrec PerformanceValueTypeINTEL
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("PERFORMANCE_VALUE_TYPE_UINT32_INTEL", PerformanceValueTypeINTEL -> ReadPrec PerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_UINT32_INTEL)
                            , ("PERFORMANCE_VALUE_TYPE_UINT64_INTEL", PerformanceValueTypeINTEL -> ReadPrec PerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_UINT64_INTEL)
                            , ("PERFORMANCE_VALUE_TYPE_FLOAT_INTEL", PerformanceValueTypeINTEL -> ReadPrec PerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_FLOAT_INTEL)
                            , ("PERFORMANCE_VALUE_TYPE_BOOL_INTEL", PerformanceValueTypeINTEL -> ReadPrec PerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_BOOL_INTEL)
                            , ("PERFORMANCE_VALUE_TYPE_STRING_INTEL", PerformanceValueTypeINTEL -> ReadPrec PerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerformanceValueTypeINTEL
PERFORMANCE_VALUE_TYPE_STRING_INTEL)]
                     ReadPrec PerformanceValueTypeINTEL
-> ReadPrec PerformanceValueTypeINTEL
-> ReadPrec PerformanceValueTypeINTEL
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec PerformanceValueTypeINTEL
-> ReadPrec PerformanceValueTypeINTEL
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "PerformanceValueTypeINTEL")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       PerformanceValueTypeINTEL -> ReadPrec PerformanceValueTypeINTEL
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> PerformanceValueTypeINTEL
PerformanceValueTypeINTEL Int32
v)))


-- No documentation found for TopLevel "VkQueryPoolCreateInfoINTEL"
type QueryPoolCreateInfoINTEL = QueryPoolPerformanceQueryCreateInfoINTEL


type INTEL_PERFORMANCE_QUERY_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_INTEL_PERFORMANCE_QUERY_SPEC_VERSION"
pattern INTEL_PERFORMANCE_QUERY_SPEC_VERSION :: forall a . Integral a => a
pattern $bINTEL_PERFORMANCE_QUERY_SPEC_VERSION :: a
$mINTEL_PERFORMANCE_QUERY_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
INTEL_PERFORMANCE_QUERY_SPEC_VERSION = 2


type INTEL_PERFORMANCE_QUERY_EXTENSION_NAME = "VK_INTEL_performance_query"

-- No documentation found for TopLevel "VK_INTEL_PERFORMANCE_QUERY_EXTENSION_NAME"
pattern INTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bINTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: a
$mINTEL_PERFORMANCE_QUERY_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
INTEL_PERFORMANCE_QUERY_EXTENSION_NAME = "VK_INTEL_performance_query"