{-# language CPP #-}
-- No documentation found for Chapter "Handles"
module Vulkan.Extensions.Handles  ( IndirectCommandsLayoutNV(..)
                                  , ValidationCacheEXT(..)
                                  , AccelerationStructureKHR(..)
                                  , AccelerationStructureNV(..)
                                  , PerformanceConfigurationINTEL(..)
                                  , BufferCollectionFUCHSIA(..)
                                  , DeferredOperationKHR(..)
                                  , CuModuleNVX(..)
                                  , CuFunctionNVX(..)
                                  , OpticalFlowSessionNV(..)
                                  , MicromapEXT(..)
                                  , ShaderEXT(..)
                                  , DisplayKHR(..)
                                  , DisplayModeKHR(..)
                                  , SurfaceKHR(..)
                                  , SwapchainKHR(..)
                                  , DebugReportCallbackEXT(..)
                                  , DebugUtilsMessengerEXT(..)
                                  , CudaModuleNV(..)
                                  , CudaFunctionNV(..)
                                  , Instance(..)
                                  , PhysicalDevice(..)
                                  , Device(..)
                                  , Queue(..)
                                  , CommandBuffer(..)
                                  , DeviceMemory(..)
                                  , CommandPool(..)
                                  , Buffer(..)
                                  , BufferView(..)
                                  , Image(..)
                                  , ImageView(..)
                                  , ShaderModule(..)
                                  , Pipeline(..)
                                  , PipelineLayout(..)
                                  , Sampler(..)
                                  , DescriptorSet(..)
                                  , DescriptorSetLayout(..)
                                  , Fence(..)
                                  , Semaphore(..)
                                  , Event(..)
                                  , QueryPool(..)
                                  , Framebuffer(..)
                                  , RenderPass(..)
                                  , PipelineCache(..)
                                  , DescriptorUpdateTemplate(..)
                                  , SamplerYcbcrConversion(..)
                                  , PrivateDataSlot(..)
                                  ) where

import GHC.Show (showParen)
import Numeric (showHex)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import Data.Word (Word64)
import Vulkan.Core10.APIConstants (HasObjectType(..))
import Vulkan.Core10.APIConstants (IsHandle)
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_ACCELERATION_STRUCTURE_NV))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_CUDA_FUNCTION_NV))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_CUDA_MODULE_NV))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_CU_FUNCTION_NVX))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_CU_MODULE_NVX))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DEBUG_UTILS_MESSENGER_EXT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DEFERRED_OPERATION_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DISPLAY_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DISPLAY_MODE_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NV))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_MICROMAP_EXT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_OPTICAL_FLOW_SESSION_NV))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SHADER_EXT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SURFACE_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SWAPCHAIN_KHR))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_VALIDATION_CACHE_EXT))
import Vulkan.Core10.Handles (Buffer(..))
import Vulkan.Core10.Handles (BufferView(..))
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandPool(..))
import Vulkan.Core10.Handles (DescriptorSet(..))
import Vulkan.Core10.Handles (DescriptorSetLayout(..))
import Vulkan.Core11.Handles (DescriptorUpdateTemplate(..))
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (DeviceMemory(..))
import Vulkan.Core10.Handles (Event(..))
import Vulkan.Core10.Handles (Fence(..))
import Vulkan.Core10.Handles (Framebuffer(..))
import Vulkan.Core10.Handles (Image(..))
import Vulkan.Core10.Handles (ImageView(..))
import Vulkan.Core10.Handles (Instance(..))
import Vulkan.Core10.Handles (PhysicalDevice(..))
import Vulkan.Core10.Handles (Pipeline(..))
import Vulkan.Core10.Handles (PipelineCache(..))
import Vulkan.Core10.Handles (PipelineLayout(..))
import Vulkan.Core13.Handles (PrivateDataSlot(..))
import Vulkan.Core10.Handles (QueryPool(..))
import Vulkan.Core10.Handles (Queue(..))
import Vulkan.Core10.Handles (RenderPass(..))
import Vulkan.Core10.Handles (Sampler(..))
import Vulkan.Core11.Handles (SamplerYcbcrConversion(..))
import Vulkan.Core10.Handles (Semaphore(..))
import Vulkan.Core10.Handles (ShaderModule(..))
-- | VkIndirectCommandsLayoutNV - Opaque handle to an indirect commands
-- layout object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_device_generated_commands VK_NV_device_generated_commands>,
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.GeneratedCommandsInfoNV',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.GeneratedCommandsMemoryRequirementsInfoNV',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.createIndirectCommandsLayoutNV',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.destroyIndirectCommandsLayoutNV'
newtype IndirectCommandsLayoutNV = IndirectCommandsLayoutNV Word64
  deriving newtype (IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
(IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool)
-> (IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool)
-> Eq IndirectCommandsLayoutNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
== :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c/= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
/= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
Eq, Eq IndirectCommandsLayoutNV
Eq IndirectCommandsLayoutNV =>
(IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Ordering)
-> (IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool)
-> (IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool)
-> (IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool)
-> (IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool)
-> (IndirectCommandsLayoutNV
    -> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV)
-> (IndirectCommandsLayoutNV
    -> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV)
-> Ord IndirectCommandsLayoutNV
IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Ordering
IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
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
$ccompare :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Ordering
compare :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Ordering
$c< :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
< :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c<= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
<= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c> :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
> :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c>= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
>= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$cmax :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
max :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
$cmin :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
min :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
Ord, Ptr IndirectCommandsLayoutNV -> IO IndirectCommandsLayoutNV
Ptr IndirectCommandsLayoutNV -> Int -> IO IndirectCommandsLayoutNV
Ptr IndirectCommandsLayoutNV
-> Int -> IndirectCommandsLayoutNV -> IO ()
Ptr IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> IO ()
IndirectCommandsLayoutNV -> Int
(IndirectCommandsLayoutNV -> Int)
-> (IndirectCommandsLayoutNV -> Int)
-> (Ptr IndirectCommandsLayoutNV
    -> Int -> IO IndirectCommandsLayoutNV)
-> (Ptr IndirectCommandsLayoutNV
    -> Int -> IndirectCommandsLayoutNV -> IO ())
-> (forall b. Ptr b -> Int -> IO IndirectCommandsLayoutNV)
-> (forall b. Ptr b -> Int -> IndirectCommandsLayoutNV -> IO ())
-> (Ptr IndirectCommandsLayoutNV -> IO IndirectCommandsLayoutNV)
-> (Ptr IndirectCommandsLayoutNV
    -> IndirectCommandsLayoutNV -> IO ())
-> Storable IndirectCommandsLayoutNV
forall b. Ptr b -> Int -> IO IndirectCommandsLayoutNV
forall b. Ptr b -> Int -> IndirectCommandsLayoutNV -> 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
$csizeOf :: IndirectCommandsLayoutNV -> Int
sizeOf :: IndirectCommandsLayoutNV -> Int
$calignment :: IndirectCommandsLayoutNV -> Int
alignment :: IndirectCommandsLayoutNV -> Int
$cpeekElemOff :: Ptr IndirectCommandsLayoutNV -> Int -> IO IndirectCommandsLayoutNV
peekElemOff :: Ptr IndirectCommandsLayoutNV -> Int -> IO IndirectCommandsLayoutNV
$cpokeElemOff :: Ptr IndirectCommandsLayoutNV
-> Int -> IndirectCommandsLayoutNV -> IO ()
pokeElemOff :: Ptr IndirectCommandsLayoutNV
-> Int -> IndirectCommandsLayoutNV -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO IndirectCommandsLayoutNV
peekByteOff :: forall b. Ptr b -> Int -> IO IndirectCommandsLayoutNV
$cpokeByteOff :: forall b. Ptr b -> Int -> IndirectCommandsLayoutNV -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> IndirectCommandsLayoutNV -> IO ()
$cpeek :: Ptr IndirectCommandsLayoutNV -> IO IndirectCommandsLayoutNV
peek :: Ptr IndirectCommandsLayoutNV -> IO IndirectCommandsLayoutNV
$cpoke :: Ptr IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> IO ()
poke :: Ptr IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> IO ()
Storable, IndirectCommandsLayoutNV
IndirectCommandsLayoutNV -> Zero IndirectCommandsLayoutNV
forall a. a -> Zero a
$czero :: IndirectCommandsLayoutNV
zero :: IndirectCommandsLayoutNV
Zero)
  deriving anyclass (Eq IndirectCommandsLayoutNV
Zero IndirectCommandsLayoutNV
(Eq IndirectCommandsLayoutNV, Zero IndirectCommandsLayoutNV) =>
IsHandle IndirectCommandsLayoutNV
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType IndirectCommandsLayoutNV where
  objectTypeAndHandle :: IndirectCommandsLayoutNV -> (ObjectType, Word64)
objectTypeAndHandle (IndirectCommandsLayoutNV Word64
h) = ( ObjectType
OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NV
                                                     , Word64
h )
instance Show IndirectCommandsLayoutNV where
  showsPrec :: Int -> IndirectCommandsLayoutNV -> ShowS
showsPrec Int
p (IndirectCommandsLayoutNV Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"IndirectCommandsLayoutNV 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkValidationCacheEXT - Opaque handle to a validation cache object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_validation_cache VK_EXT_validation_cache>,
-- 'Vulkan.Extensions.VK_EXT_validation_cache.ShaderModuleValidationCacheCreateInfoEXT',
-- 'Vulkan.Extensions.VK_EXT_validation_cache.createValidationCacheEXT',
-- 'Vulkan.Extensions.VK_EXT_validation_cache.destroyValidationCacheEXT',
-- 'Vulkan.Extensions.VK_EXT_validation_cache.getValidationCacheDataEXT',
-- 'Vulkan.Extensions.VK_EXT_validation_cache.mergeValidationCachesEXT'
newtype ValidationCacheEXT = ValidationCacheEXT Word64
  deriving newtype (ValidationCacheEXT -> ValidationCacheEXT -> Bool
(ValidationCacheEXT -> ValidationCacheEXT -> Bool)
-> (ValidationCacheEXT -> ValidationCacheEXT -> Bool)
-> Eq ValidationCacheEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
== :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c/= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
/= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
Eq, Eq ValidationCacheEXT
Eq ValidationCacheEXT =>
(ValidationCacheEXT -> ValidationCacheEXT -> Ordering)
-> (ValidationCacheEXT -> ValidationCacheEXT -> Bool)
-> (ValidationCacheEXT -> ValidationCacheEXT -> Bool)
-> (ValidationCacheEXT -> ValidationCacheEXT -> Bool)
-> (ValidationCacheEXT -> ValidationCacheEXT -> Bool)
-> (ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT)
-> (ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT)
-> Ord ValidationCacheEXT
ValidationCacheEXT -> ValidationCacheEXT -> Bool
ValidationCacheEXT -> ValidationCacheEXT -> Ordering
ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
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
$ccompare :: ValidationCacheEXT -> ValidationCacheEXT -> Ordering
compare :: ValidationCacheEXT -> ValidationCacheEXT -> Ordering
$c< :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
< :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c<= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
<= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c> :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
> :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c>= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
>= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$cmax :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
max :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
$cmin :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
min :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
Ord, Ptr ValidationCacheEXT -> IO ValidationCacheEXT
Ptr ValidationCacheEXT -> Int -> IO ValidationCacheEXT
Ptr ValidationCacheEXT -> Int -> ValidationCacheEXT -> IO ()
Ptr ValidationCacheEXT -> ValidationCacheEXT -> IO ()
ValidationCacheEXT -> Int
(ValidationCacheEXT -> Int)
-> (ValidationCacheEXT -> Int)
-> (Ptr ValidationCacheEXT -> Int -> IO ValidationCacheEXT)
-> (Ptr ValidationCacheEXT -> Int -> ValidationCacheEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO ValidationCacheEXT)
-> (forall b. Ptr b -> Int -> ValidationCacheEXT -> IO ())
-> (Ptr ValidationCacheEXT -> IO ValidationCacheEXT)
-> (Ptr ValidationCacheEXT -> ValidationCacheEXT -> IO ())
-> Storable ValidationCacheEXT
forall b. Ptr b -> Int -> IO ValidationCacheEXT
forall b. Ptr b -> Int -> ValidationCacheEXT -> 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
$csizeOf :: ValidationCacheEXT -> Int
sizeOf :: ValidationCacheEXT -> Int
$calignment :: ValidationCacheEXT -> Int
alignment :: ValidationCacheEXT -> Int
$cpeekElemOff :: Ptr ValidationCacheEXT -> Int -> IO ValidationCacheEXT
peekElemOff :: Ptr ValidationCacheEXT -> Int -> IO ValidationCacheEXT
$cpokeElemOff :: Ptr ValidationCacheEXT -> Int -> ValidationCacheEXT -> IO ()
pokeElemOff :: Ptr ValidationCacheEXT -> Int -> ValidationCacheEXT -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ValidationCacheEXT
peekByteOff :: forall b. Ptr b -> Int -> IO ValidationCacheEXT
$cpokeByteOff :: forall b. Ptr b -> Int -> ValidationCacheEXT -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> ValidationCacheEXT -> IO ()
$cpeek :: Ptr ValidationCacheEXT -> IO ValidationCacheEXT
peek :: Ptr ValidationCacheEXT -> IO ValidationCacheEXT
$cpoke :: Ptr ValidationCacheEXT -> ValidationCacheEXT -> IO ()
poke :: Ptr ValidationCacheEXT -> ValidationCacheEXT -> IO ()
Storable, ValidationCacheEXT
ValidationCacheEXT -> Zero ValidationCacheEXT
forall a. a -> Zero a
$czero :: ValidationCacheEXT
zero :: ValidationCacheEXT
Zero)
  deriving anyclass (Eq ValidationCacheEXT
Zero ValidationCacheEXT
(Eq ValidationCacheEXT, Zero ValidationCacheEXT) =>
IsHandle ValidationCacheEXT
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType ValidationCacheEXT where
  objectTypeAndHandle :: ValidationCacheEXT -> (ObjectType, Word64)
objectTypeAndHandle (ValidationCacheEXT Word64
h) = ( ObjectType
OBJECT_TYPE_VALIDATION_CACHE_EXT
                                               , Word64
h )
instance Show ValidationCacheEXT where
  showsPrec :: Int -> ValidationCacheEXT -> ShowS
showsPrec Int
p (ValidationCacheEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"ValidationCacheEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkAccelerationStructureKHR - Opaque handle to an acceleration structure
-- object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_acceleration_structure VK_KHR_acceleration_structure>,
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.AccelerationStructureBuildGeometryInfoKHR',
-- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.AccelerationStructureCaptureDescriptorDataInfoEXT',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.AccelerationStructureDeviceAddressInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.CopyAccelerationStructureInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.CopyAccelerationStructureToMemoryInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.CopyMemoryToAccelerationStructureInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.WriteDescriptorSetAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.cmdWriteAccelerationStructuresPropertiesKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.createAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.destroyAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.writeAccelerationStructuresPropertiesKHR'
newtype AccelerationStructureKHR = AccelerationStructureKHR Word64
  deriving newtype (AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
(AccelerationStructureKHR -> AccelerationStructureKHR -> Bool)
-> (AccelerationStructureKHR -> AccelerationStructureKHR -> Bool)
-> Eq AccelerationStructureKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
== :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c/= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
/= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
Eq, Eq AccelerationStructureKHR
Eq AccelerationStructureKHR =>
(AccelerationStructureKHR -> AccelerationStructureKHR -> Ordering)
-> (AccelerationStructureKHR -> AccelerationStructureKHR -> Bool)
-> (AccelerationStructureKHR -> AccelerationStructureKHR -> Bool)
-> (AccelerationStructureKHR -> AccelerationStructureKHR -> Bool)
-> (AccelerationStructureKHR -> AccelerationStructureKHR -> Bool)
-> (AccelerationStructureKHR
    -> AccelerationStructureKHR -> AccelerationStructureKHR)
-> (AccelerationStructureKHR
    -> AccelerationStructureKHR -> AccelerationStructureKHR)
-> Ord AccelerationStructureKHR
AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
AccelerationStructureKHR -> AccelerationStructureKHR -> Ordering
AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
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
$ccompare :: AccelerationStructureKHR -> AccelerationStructureKHR -> Ordering
compare :: AccelerationStructureKHR -> AccelerationStructureKHR -> Ordering
$c< :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
< :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c<= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
<= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c> :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
> :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c>= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
>= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$cmax :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
max :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
$cmin :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
min :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
Ord, Ptr AccelerationStructureKHR -> IO AccelerationStructureKHR
Ptr AccelerationStructureKHR -> Int -> IO AccelerationStructureKHR
Ptr AccelerationStructureKHR
-> Int -> AccelerationStructureKHR -> IO ()
Ptr AccelerationStructureKHR -> AccelerationStructureKHR -> IO ()
AccelerationStructureKHR -> Int
(AccelerationStructureKHR -> Int)
-> (AccelerationStructureKHR -> Int)
-> (Ptr AccelerationStructureKHR
    -> Int -> IO AccelerationStructureKHR)
-> (Ptr AccelerationStructureKHR
    -> Int -> AccelerationStructureKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO AccelerationStructureKHR)
-> (forall b. Ptr b -> Int -> AccelerationStructureKHR -> IO ())
-> (Ptr AccelerationStructureKHR -> IO AccelerationStructureKHR)
-> (Ptr AccelerationStructureKHR
    -> AccelerationStructureKHR -> IO ())
-> Storable AccelerationStructureKHR
forall b. Ptr b -> Int -> IO AccelerationStructureKHR
forall b. Ptr b -> Int -> AccelerationStructureKHR -> 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
$csizeOf :: AccelerationStructureKHR -> Int
sizeOf :: AccelerationStructureKHR -> Int
$calignment :: AccelerationStructureKHR -> Int
alignment :: AccelerationStructureKHR -> Int
$cpeekElemOff :: Ptr AccelerationStructureKHR -> Int -> IO AccelerationStructureKHR
peekElemOff :: Ptr AccelerationStructureKHR -> Int -> IO AccelerationStructureKHR
$cpokeElemOff :: Ptr AccelerationStructureKHR
-> Int -> AccelerationStructureKHR -> IO ()
pokeElemOff :: Ptr AccelerationStructureKHR
-> Int -> AccelerationStructureKHR -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureKHR
peekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureKHR
$cpokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureKHR -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureKHR -> IO ()
$cpeek :: Ptr AccelerationStructureKHR -> IO AccelerationStructureKHR
peek :: Ptr AccelerationStructureKHR -> IO AccelerationStructureKHR
$cpoke :: Ptr AccelerationStructureKHR -> AccelerationStructureKHR -> IO ()
poke :: Ptr AccelerationStructureKHR -> AccelerationStructureKHR -> IO ()
Storable, AccelerationStructureKHR
AccelerationStructureKHR -> Zero AccelerationStructureKHR
forall a. a -> Zero a
$czero :: AccelerationStructureKHR
zero :: AccelerationStructureKHR
Zero)
  deriving anyclass (Eq AccelerationStructureKHR
Zero AccelerationStructureKHR
(Eq AccelerationStructureKHR, Zero AccelerationStructureKHR) =>
IsHandle AccelerationStructureKHR
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType AccelerationStructureKHR where
  objectTypeAndHandle :: AccelerationStructureKHR -> (ObjectType, Word64)
objectTypeAndHandle (AccelerationStructureKHR Word64
h) = ( ObjectType
OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR
                                                     , Word64
h )
instance Show AccelerationStructureKHR where
  showsPrec :: Int -> AccelerationStructureKHR -> ShowS
showsPrec Int
p (AccelerationStructureKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"AccelerationStructureKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkAccelerationStructureNV - Opaque handle to an acceleration structure
-- object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_ray_tracing VK_NV_ray_tracing>,
-- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.AccelerationStructureCaptureDescriptorDataInfoEXT',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.AccelerationStructureMemoryRequirementsInfoNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.BindAccelerationStructureMemoryInfoNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.WriteDescriptorSetAccelerationStructureNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdBuildAccelerationStructureNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdCopyAccelerationStructureNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdWriteAccelerationStructuresPropertiesNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.createAccelerationStructureNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.destroyAccelerationStructureNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.getAccelerationStructureHandleNV'
newtype AccelerationStructureNV = AccelerationStructureNV Word64
  deriving newtype (AccelerationStructureNV -> AccelerationStructureNV -> Bool
(AccelerationStructureNV -> AccelerationStructureNV -> Bool)
-> (AccelerationStructureNV -> AccelerationStructureNV -> Bool)
-> Eq AccelerationStructureNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
== :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c/= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
/= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
Eq, Eq AccelerationStructureNV
Eq AccelerationStructureNV =>
(AccelerationStructureNV -> AccelerationStructureNV -> Ordering)
-> (AccelerationStructureNV -> AccelerationStructureNV -> Bool)
-> (AccelerationStructureNV -> AccelerationStructureNV -> Bool)
-> (AccelerationStructureNV -> AccelerationStructureNV -> Bool)
-> (AccelerationStructureNV -> AccelerationStructureNV -> Bool)
-> (AccelerationStructureNV
    -> AccelerationStructureNV -> AccelerationStructureNV)
-> (AccelerationStructureNV
    -> AccelerationStructureNV -> AccelerationStructureNV)
-> Ord AccelerationStructureNV
AccelerationStructureNV -> AccelerationStructureNV -> Bool
AccelerationStructureNV -> AccelerationStructureNV -> Ordering
AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
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
$ccompare :: AccelerationStructureNV -> AccelerationStructureNV -> Ordering
compare :: AccelerationStructureNV -> AccelerationStructureNV -> Ordering
$c< :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
< :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c<= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
<= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c> :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
> :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$c>= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
>= :: AccelerationStructureNV -> AccelerationStructureNV -> Bool
$cmax :: AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
max :: AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
$cmin :: AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
min :: AccelerationStructureNV
-> AccelerationStructureNV -> AccelerationStructureNV
Ord, Ptr AccelerationStructureNV -> IO AccelerationStructureNV
Ptr AccelerationStructureNV -> Int -> IO AccelerationStructureNV
Ptr AccelerationStructureNV
-> Int -> AccelerationStructureNV -> IO ()
Ptr AccelerationStructureNV -> AccelerationStructureNV -> IO ()
AccelerationStructureNV -> Int
(AccelerationStructureNV -> Int)
-> (AccelerationStructureNV -> Int)
-> (Ptr AccelerationStructureNV
    -> Int -> IO AccelerationStructureNV)
-> (Ptr AccelerationStructureNV
    -> Int -> AccelerationStructureNV -> IO ())
-> (forall b. Ptr b -> Int -> IO AccelerationStructureNV)
-> (forall b. Ptr b -> Int -> AccelerationStructureNV -> IO ())
-> (Ptr AccelerationStructureNV -> IO AccelerationStructureNV)
-> (Ptr AccelerationStructureNV
    -> AccelerationStructureNV -> IO ())
-> Storable AccelerationStructureNV
forall b. Ptr b -> Int -> IO AccelerationStructureNV
forall b. Ptr b -> Int -> AccelerationStructureNV -> 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
$csizeOf :: AccelerationStructureNV -> Int
sizeOf :: AccelerationStructureNV -> Int
$calignment :: AccelerationStructureNV -> Int
alignment :: AccelerationStructureNV -> Int
$cpeekElemOff :: Ptr AccelerationStructureNV -> Int -> IO AccelerationStructureNV
peekElemOff :: Ptr AccelerationStructureNV -> Int -> IO AccelerationStructureNV
$cpokeElemOff :: Ptr AccelerationStructureNV
-> Int -> AccelerationStructureNV -> IO ()
pokeElemOff :: Ptr AccelerationStructureNV
-> Int -> AccelerationStructureNV -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureNV
peekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureNV
$cpokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureNV -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureNV -> IO ()
$cpeek :: Ptr AccelerationStructureNV -> IO AccelerationStructureNV
peek :: Ptr AccelerationStructureNV -> IO AccelerationStructureNV
$cpoke :: Ptr AccelerationStructureNV -> AccelerationStructureNV -> IO ()
poke :: Ptr AccelerationStructureNV -> AccelerationStructureNV -> IO ()
Storable, AccelerationStructureNV
AccelerationStructureNV -> Zero AccelerationStructureNV
forall a. a -> Zero a
$czero :: AccelerationStructureNV
zero :: AccelerationStructureNV
Zero)
  deriving anyclass (Eq AccelerationStructureNV
Zero AccelerationStructureNV
(Eq AccelerationStructureNV, Zero AccelerationStructureNV) =>
IsHandle AccelerationStructureNV
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType AccelerationStructureNV where
  objectTypeAndHandle :: AccelerationStructureNV -> (ObjectType, Word64)
objectTypeAndHandle (AccelerationStructureNV Word64
h) = ( ObjectType
OBJECT_TYPE_ACCELERATION_STRUCTURE_NV
                                                    , Word64
h )
instance Show AccelerationStructureNV where
  showsPrec :: Int -> AccelerationStructureNV -> ShowS
showsPrec Int
p (AccelerationStructureNV Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"AccelerationStructureNV 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkPerformanceConfigurationINTEL - Device configuration for performance
-- queries
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_INTEL_performance_query VK_INTEL_performance_query>,
-- 'Vulkan.Extensions.VK_INTEL_performance_query.acquirePerformanceConfigurationINTEL',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.queueSetPerformanceConfigurationINTEL',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.releasePerformanceConfigurationINTEL'
newtype PerformanceConfigurationINTEL = PerformanceConfigurationINTEL Word64
  deriving newtype (PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
(PerformanceConfigurationINTEL
 -> PerformanceConfigurationINTEL -> Bool)
-> (PerformanceConfigurationINTEL
    -> PerformanceConfigurationINTEL -> Bool)
-> Eq PerformanceConfigurationINTEL
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
== :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c/= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
/= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
Eq, Eq PerformanceConfigurationINTEL
Eq PerformanceConfigurationINTEL =>
(PerformanceConfigurationINTEL
 -> PerformanceConfigurationINTEL -> Ordering)
-> (PerformanceConfigurationINTEL
    -> PerformanceConfigurationINTEL -> Bool)
-> (PerformanceConfigurationINTEL
    -> PerformanceConfigurationINTEL -> Bool)
-> (PerformanceConfigurationINTEL
    -> PerformanceConfigurationINTEL -> Bool)
-> (PerformanceConfigurationINTEL
    -> PerformanceConfigurationINTEL -> Bool)
-> (PerformanceConfigurationINTEL
    -> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL)
-> (PerformanceConfigurationINTEL
    -> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL)
-> Ord PerformanceConfigurationINTEL
PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Ordering
PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
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
$ccompare :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Ordering
compare :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Ordering
$c< :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
< :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c<= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
<= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c> :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
> :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c>= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
>= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$cmax :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
max :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
$cmin :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
min :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
Ord, Ptr PerformanceConfigurationINTEL
-> IO PerformanceConfigurationINTEL
Ptr PerformanceConfigurationINTEL
-> Int -> IO PerformanceConfigurationINTEL
Ptr PerformanceConfigurationINTEL
-> Int -> PerformanceConfigurationINTEL -> IO ()
Ptr PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> IO ()
PerformanceConfigurationINTEL -> Int
(PerformanceConfigurationINTEL -> Int)
-> (PerformanceConfigurationINTEL -> Int)
-> (Ptr PerformanceConfigurationINTEL
    -> Int -> IO PerformanceConfigurationINTEL)
-> (Ptr PerformanceConfigurationINTEL
    -> Int -> PerformanceConfigurationINTEL -> IO ())
-> (forall b. Ptr b -> Int -> IO PerformanceConfigurationINTEL)
-> (forall b.
    Ptr b -> Int -> PerformanceConfigurationINTEL -> IO ())
-> (Ptr PerformanceConfigurationINTEL
    -> IO PerformanceConfigurationINTEL)
-> (Ptr PerformanceConfigurationINTEL
    -> PerformanceConfigurationINTEL -> IO ())
-> Storable PerformanceConfigurationINTEL
forall b. Ptr b -> Int -> IO PerformanceConfigurationINTEL
forall b. Ptr b -> Int -> PerformanceConfigurationINTEL -> 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
$csizeOf :: PerformanceConfigurationINTEL -> Int
sizeOf :: PerformanceConfigurationINTEL -> Int
$calignment :: PerformanceConfigurationINTEL -> Int
alignment :: PerformanceConfigurationINTEL -> Int
$cpeekElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> IO PerformanceConfigurationINTEL
peekElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> IO PerformanceConfigurationINTEL
$cpokeElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> PerformanceConfigurationINTEL -> IO ()
pokeElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> PerformanceConfigurationINTEL -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceConfigurationINTEL
peekByteOff :: forall b. Ptr b -> Int -> IO PerformanceConfigurationINTEL
$cpokeByteOff :: forall b. Ptr b -> Int -> PerformanceConfigurationINTEL -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> PerformanceConfigurationINTEL -> IO ()
$cpeek :: Ptr PerformanceConfigurationINTEL
-> IO PerformanceConfigurationINTEL
peek :: Ptr PerformanceConfigurationINTEL
-> IO PerformanceConfigurationINTEL
$cpoke :: Ptr PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> IO ()
poke :: Ptr PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> IO ()
Storable, PerformanceConfigurationINTEL
PerformanceConfigurationINTEL -> Zero PerformanceConfigurationINTEL
forall a. a -> Zero a
$czero :: PerformanceConfigurationINTEL
zero :: PerformanceConfigurationINTEL
Zero)
  deriving anyclass (Eq PerformanceConfigurationINTEL
Zero PerformanceConfigurationINTEL
(Eq PerformanceConfigurationINTEL,
 Zero PerformanceConfigurationINTEL) =>
IsHandle PerformanceConfigurationINTEL
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType PerformanceConfigurationINTEL where
  objectTypeAndHandle :: PerformanceConfigurationINTEL -> (ObjectType, Word64)
objectTypeAndHandle (PerformanceConfigurationINTEL Word64
h) = ( ObjectType
OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL
                                                          , Word64
h )
instance Show PerformanceConfigurationINTEL where
  showsPrec :: Int -> PerformanceConfigurationINTEL -> ShowS
showsPrec Int
p (PerformanceConfigurationINTEL Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"PerformanceConfigurationINTEL 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkBufferCollectionFUCHSIA - Opaque handle to a buffer collection object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_FUCHSIA_buffer_collection VK_FUCHSIA_buffer_collection>,
-- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionBufferCreateInfoFUCHSIA',
-- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionImageCreateInfoFUCHSIA',
-- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.ImportMemoryBufferCollectionFUCHSIA',
-- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.createBufferCollectionFUCHSIA',
-- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.destroyBufferCollectionFUCHSIA',
-- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.getBufferCollectionPropertiesFUCHSIA',
-- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.setBufferCollectionBufferConstraintsFUCHSIA',
-- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.setBufferCollectionImageConstraintsFUCHSIA'
newtype BufferCollectionFUCHSIA = BufferCollectionFUCHSIA Word64
  deriving newtype (BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
(BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool)
-> (BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool)
-> Eq BufferCollectionFUCHSIA
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
== :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c/= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
/= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
Eq, Eq BufferCollectionFUCHSIA
Eq BufferCollectionFUCHSIA =>
(BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Ordering)
-> (BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool)
-> (BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool)
-> (BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool)
-> (BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool)
-> (BufferCollectionFUCHSIA
    -> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA)
-> (BufferCollectionFUCHSIA
    -> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA)
-> Ord BufferCollectionFUCHSIA
BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Ordering
BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
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
$ccompare :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Ordering
compare :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Ordering
$c< :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
< :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c<= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
<= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c> :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
> :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$c>= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
>= :: BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> Bool
$cmax :: BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
max :: BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
$cmin :: BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
min :: BufferCollectionFUCHSIA
-> BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA
Ord, Ptr BufferCollectionFUCHSIA -> IO BufferCollectionFUCHSIA
Ptr BufferCollectionFUCHSIA -> Int -> IO BufferCollectionFUCHSIA
Ptr BufferCollectionFUCHSIA
-> Int -> BufferCollectionFUCHSIA -> IO ()
Ptr BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> IO ()
BufferCollectionFUCHSIA -> Int
(BufferCollectionFUCHSIA -> Int)
-> (BufferCollectionFUCHSIA -> Int)
-> (Ptr BufferCollectionFUCHSIA
    -> Int -> IO BufferCollectionFUCHSIA)
-> (Ptr BufferCollectionFUCHSIA
    -> Int -> BufferCollectionFUCHSIA -> IO ())
-> (forall b. Ptr b -> Int -> IO BufferCollectionFUCHSIA)
-> (forall b. Ptr b -> Int -> BufferCollectionFUCHSIA -> IO ())
-> (Ptr BufferCollectionFUCHSIA -> IO BufferCollectionFUCHSIA)
-> (Ptr BufferCollectionFUCHSIA
    -> BufferCollectionFUCHSIA -> IO ())
-> Storable BufferCollectionFUCHSIA
forall b. Ptr b -> Int -> IO BufferCollectionFUCHSIA
forall b. Ptr b -> Int -> BufferCollectionFUCHSIA -> 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
$csizeOf :: BufferCollectionFUCHSIA -> Int
sizeOf :: BufferCollectionFUCHSIA -> Int
$calignment :: BufferCollectionFUCHSIA -> Int
alignment :: BufferCollectionFUCHSIA -> Int
$cpeekElemOff :: Ptr BufferCollectionFUCHSIA -> Int -> IO BufferCollectionFUCHSIA
peekElemOff :: Ptr BufferCollectionFUCHSIA -> Int -> IO BufferCollectionFUCHSIA
$cpokeElemOff :: Ptr BufferCollectionFUCHSIA
-> Int -> BufferCollectionFUCHSIA -> IO ()
pokeElemOff :: Ptr BufferCollectionFUCHSIA
-> Int -> BufferCollectionFUCHSIA -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO BufferCollectionFUCHSIA
peekByteOff :: forall b. Ptr b -> Int -> IO BufferCollectionFUCHSIA
$cpokeByteOff :: forall b. Ptr b -> Int -> BufferCollectionFUCHSIA -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> BufferCollectionFUCHSIA -> IO ()
$cpeek :: Ptr BufferCollectionFUCHSIA -> IO BufferCollectionFUCHSIA
peek :: Ptr BufferCollectionFUCHSIA -> IO BufferCollectionFUCHSIA
$cpoke :: Ptr BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> IO ()
poke :: Ptr BufferCollectionFUCHSIA -> BufferCollectionFUCHSIA -> IO ()
Storable, BufferCollectionFUCHSIA
BufferCollectionFUCHSIA -> Zero BufferCollectionFUCHSIA
forall a. a -> Zero a
$czero :: BufferCollectionFUCHSIA
zero :: BufferCollectionFUCHSIA
Zero)
  deriving anyclass (Eq BufferCollectionFUCHSIA
Zero BufferCollectionFUCHSIA
(Eq BufferCollectionFUCHSIA, Zero BufferCollectionFUCHSIA) =>
IsHandle BufferCollectionFUCHSIA
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType BufferCollectionFUCHSIA where
  objectTypeAndHandle :: BufferCollectionFUCHSIA -> (ObjectType, Word64)
objectTypeAndHandle (BufferCollectionFUCHSIA Word64
h) = ( ObjectType
OBJECT_TYPE_BUFFER_COLLECTION_FUCHSIA
                                                    , Word64
h )
instance Show BufferCollectionFUCHSIA where
  showsPrec :: Int -> BufferCollectionFUCHSIA -> ShowS
showsPrec Int
p (BufferCollectionFUCHSIA Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"BufferCollectionFUCHSIA 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkDeferredOperationKHR - A deferred operation
--
-- = Description
--
-- This handle refers to a tracking structure which manages the execution
-- state for a deferred command.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_deferred_host_operations VK_KHR_deferred_host_operations>,
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.buildAccelerationStructuresKHR',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.buildMicromapsEXT',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.copyAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.copyAccelerationStructureToMemoryKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.copyMemoryToAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.copyMemoryToMicromapEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.copyMicromapEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.copyMicromapToMemoryEXT',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.createDeferredOperationKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing_pipeline.createRayTracingPipelinesKHR',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.deferredOperationJoinKHR',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.destroyDeferredOperationKHR',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.getDeferredOperationMaxConcurrencyKHR',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.getDeferredOperationResultKHR'
newtype DeferredOperationKHR = DeferredOperationKHR Word64
  deriving newtype (DeferredOperationKHR -> DeferredOperationKHR -> Bool
(DeferredOperationKHR -> DeferredOperationKHR -> Bool)
-> (DeferredOperationKHR -> DeferredOperationKHR -> Bool)
-> Eq DeferredOperationKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
== :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c/= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
/= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
Eq, Eq DeferredOperationKHR
Eq DeferredOperationKHR =>
(DeferredOperationKHR -> DeferredOperationKHR -> Ordering)
-> (DeferredOperationKHR -> DeferredOperationKHR -> Bool)
-> (DeferredOperationKHR -> DeferredOperationKHR -> Bool)
-> (DeferredOperationKHR -> DeferredOperationKHR -> Bool)
-> (DeferredOperationKHR -> DeferredOperationKHR -> Bool)
-> (DeferredOperationKHR
    -> DeferredOperationKHR -> DeferredOperationKHR)
-> (DeferredOperationKHR
    -> DeferredOperationKHR -> DeferredOperationKHR)
-> Ord DeferredOperationKHR
DeferredOperationKHR -> DeferredOperationKHR -> Bool
DeferredOperationKHR -> DeferredOperationKHR -> Ordering
DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
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
$ccompare :: DeferredOperationKHR -> DeferredOperationKHR -> Ordering
compare :: DeferredOperationKHR -> DeferredOperationKHR -> Ordering
$c< :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
< :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c<= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
<= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c> :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
> :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c>= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
>= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$cmax :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
max :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
$cmin :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
min :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
Ord, Ptr DeferredOperationKHR -> IO DeferredOperationKHR
Ptr DeferredOperationKHR -> Int -> IO DeferredOperationKHR
Ptr DeferredOperationKHR -> Int -> DeferredOperationKHR -> IO ()
Ptr DeferredOperationKHR -> DeferredOperationKHR -> IO ()
DeferredOperationKHR -> Int
(DeferredOperationKHR -> Int)
-> (DeferredOperationKHR -> Int)
-> (Ptr DeferredOperationKHR -> Int -> IO DeferredOperationKHR)
-> (Ptr DeferredOperationKHR
    -> Int -> DeferredOperationKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO DeferredOperationKHR)
-> (forall b. Ptr b -> Int -> DeferredOperationKHR -> IO ())
-> (Ptr DeferredOperationKHR -> IO DeferredOperationKHR)
-> (Ptr DeferredOperationKHR -> DeferredOperationKHR -> IO ())
-> Storable DeferredOperationKHR
forall b. Ptr b -> Int -> IO DeferredOperationKHR
forall b. Ptr b -> Int -> DeferredOperationKHR -> 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
$csizeOf :: DeferredOperationKHR -> Int
sizeOf :: DeferredOperationKHR -> Int
$calignment :: DeferredOperationKHR -> Int
alignment :: DeferredOperationKHR -> Int
$cpeekElemOff :: Ptr DeferredOperationKHR -> Int -> IO DeferredOperationKHR
peekElemOff :: Ptr DeferredOperationKHR -> Int -> IO DeferredOperationKHR
$cpokeElemOff :: Ptr DeferredOperationKHR -> Int -> DeferredOperationKHR -> IO ()
pokeElemOff :: Ptr DeferredOperationKHR -> Int -> DeferredOperationKHR -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DeferredOperationKHR
peekByteOff :: forall b. Ptr b -> Int -> IO DeferredOperationKHR
$cpokeByteOff :: forall b. Ptr b -> Int -> DeferredOperationKHR -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> DeferredOperationKHR -> IO ()
$cpeek :: Ptr DeferredOperationKHR -> IO DeferredOperationKHR
peek :: Ptr DeferredOperationKHR -> IO DeferredOperationKHR
$cpoke :: Ptr DeferredOperationKHR -> DeferredOperationKHR -> IO ()
poke :: Ptr DeferredOperationKHR -> DeferredOperationKHR -> IO ()
Storable, DeferredOperationKHR
DeferredOperationKHR -> Zero DeferredOperationKHR
forall a. a -> Zero a
$czero :: DeferredOperationKHR
zero :: DeferredOperationKHR
Zero)
  deriving anyclass (Eq DeferredOperationKHR
Zero DeferredOperationKHR
(Eq DeferredOperationKHR, Zero DeferredOperationKHR) =>
IsHandle DeferredOperationKHR
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType DeferredOperationKHR where
  objectTypeAndHandle :: DeferredOperationKHR -> (ObjectType, Word64)
objectTypeAndHandle (DeferredOperationKHR Word64
h) = ( ObjectType
OBJECT_TYPE_DEFERRED_OPERATION_KHR
                                                 , Word64
h )
instance Show DeferredOperationKHR where
  showsPrec :: Int -> DeferredOperationKHR -> ShowS
showsPrec Int
p (DeferredOperationKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DeferredOperationKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkCuModuleNVX - Stub description of VkCuModuleNVX
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NVX_binary_import VK_NVX_binary_import>,
-- 'Vulkan.Extensions.VK_NVX_binary_import.CuFunctionCreateInfoNVX',
-- 'Vulkan.Extensions.VK_NVX_binary_import.createCuModuleNVX',
-- 'Vulkan.Extensions.VK_NVX_binary_import.destroyCuModuleNVX'
newtype CuModuleNVX = CuModuleNVX Word64
  deriving newtype (CuModuleNVX -> CuModuleNVX -> Bool
(CuModuleNVX -> CuModuleNVX -> Bool)
-> (CuModuleNVX -> CuModuleNVX -> Bool) -> Eq CuModuleNVX
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CuModuleNVX -> CuModuleNVX -> Bool
== :: CuModuleNVX -> CuModuleNVX -> Bool
$c/= :: CuModuleNVX -> CuModuleNVX -> Bool
/= :: CuModuleNVX -> CuModuleNVX -> Bool
Eq, Eq CuModuleNVX
Eq CuModuleNVX =>
(CuModuleNVX -> CuModuleNVX -> Ordering)
-> (CuModuleNVX -> CuModuleNVX -> Bool)
-> (CuModuleNVX -> CuModuleNVX -> Bool)
-> (CuModuleNVX -> CuModuleNVX -> Bool)
-> (CuModuleNVX -> CuModuleNVX -> Bool)
-> (CuModuleNVX -> CuModuleNVX -> CuModuleNVX)
-> (CuModuleNVX -> CuModuleNVX -> CuModuleNVX)
-> Ord CuModuleNVX
CuModuleNVX -> CuModuleNVX -> Bool
CuModuleNVX -> CuModuleNVX -> Ordering
CuModuleNVX -> CuModuleNVX -> CuModuleNVX
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
$ccompare :: CuModuleNVX -> CuModuleNVX -> Ordering
compare :: CuModuleNVX -> CuModuleNVX -> Ordering
$c< :: CuModuleNVX -> CuModuleNVX -> Bool
< :: CuModuleNVX -> CuModuleNVX -> Bool
$c<= :: CuModuleNVX -> CuModuleNVX -> Bool
<= :: CuModuleNVX -> CuModuleNVX -> Bool
$c> :: CuModuleNVX -> CuModuleNVX -> Bool
> :: CuModuleNVX -> CuModuleNVX -> Bool
$c>= :: CuModuleNVX -> CuModuleNVX -> Bool
>= :: CuModuleNVX -> CuModuleNVX -> Bool
$cmax :: CuModuleNVX -> CuModuleNVX -> CuModuleNVX
max :: CuModuleNVX -> CuModuleNVX -> CuModuleNVX
$cmin :: CuModuleNVX -> CuModuleNVX -> CuModuleNVX
min :: CuModuleNVX -> CuModuleNVX -> CuModuleNVX
Ord, Ptr CuModuleNVX -> IO CuModuleNVX
Ptr CuModuleNVX -> Int -> IO CuModuleNVX
Ptr CuModuleNVX -> Int -> CuModuleNVX -> IO ()
Ptr CuModuleNVX -> CuModuleNVX -> IO ()
CuModuleNVX -> Int
(CuModuleNVX -> Int)
-> (CuModuleNVX -> Int)
-> (Ptr CuModuleNVX -> Int -> IO CuModuleNVX)
-> (Ptr CuModuleNVX -> Int -> CuModuleNVX -> IO ())
-> (forall b. Ptr b -> Int -> IO CuModuleNVX)
-> (forall b. Ptr b -> Int -> CuModuleNVX -> IO ())
-> (Ptr CuModuleNVX -> IO CuModuleNVX)
-> (Ptr CuModuleNVX -> CuModuleNVX -> IO ())
-> Storable CuModuleNVX
forall b. Ptr b -> Int -> IO CuModuleNVX
forall b. Ptr b -> Int -> CuModuleNVX -> 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
$csizeOf :: CuModuleNVX -> Int
sizeOf :: CuModuleNVX -> Int
$calignment :: CuModuleNVX -> Int
alignment :: CuModuleNVX -> Int
$cpeekElemOff :: Ptr CuModuleNVX -> Int -> IO CuModuleNVX
peekElemOff :: Ptr CuModuleNVX -> Int -> IO CuModuleNVX
$cpokeElemOff :: Ptr CuModuleNVX -> Int -> CuModuleNVX -> IO ()
pokeElemOff :: Ptr CuModuleNVX -> Int -> CuModuleNVX -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CuModuleNVX
peekByteOff :: forall b. Ptr b -> Int -> IO CuModuleNVX
$cpokeByteOff :: forall b. Ptr b -> Int -> CuModuleNVX -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> CuModuleNVX -> IO ()
$cpeek :: Ptr CuModuleNVX -> IO CuModuleNVX
peek :: Ptr CuModuleNVX -> IO CuModuleNVX
$cpoke :: Ptr CuModuleNVX -> CuModuleNVX -> IO ()
poke :: Ptr CuModuleNVX -> CuModuleNVX -> IO ()
Storable, CuModuleNVX
CuModuleNVX -> Zero CuModuleNVX
forall a. a -> Zero a
$czero :: CuModuleNVX
zero :: CuModuleNVX
Zero)
  deriving anyclass (Eq CuModuleNVX
Zero CuModuleNVX
(Eq CuModuleNVX, Zero CuModuleNVX) => IsHandle CuModuleNVX
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType CuModuleNVX where
  objectTypeAndHandle :: CuModuleNVX -> (ObjectType, Word64)
objectTypeAndHandle (CuModuleNVX Word64
h) = (ObjectType
OBJECT_TYPE_CU_MODULE_NVX, Word64
h)
instance Show CuModuleNVX where
  showsPrec :: Int -> CuModuleNVX -> ShowS
showsPrec Int
p (CuModuleNVX Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"CuModuleNVX 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkCuFunctionNVX - Stub description of VkCuFunctionNVX
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NVX_binary_import VK_NVX_binary_import>,
-- 'Vulkan.Extensions.VK_NVX_binary_import.CuLaunchInfoNVX',
-- 'Vulkan.Extensions.VK_NVX_binary_import.createCuFunctionNVX',
-- 'Vulkan.Extensions.VK_NVX_binary_import.destroyCuFunctionNVX'
newtype CuFunctionNVX = CuFunctionNVX Word64
  deriving newtype (CuFunctionNVX -> CuFunctionNVX -> Bool
(CuFunctionNVX -> CuFunctionNVX -> Bool)
-> (CuFunctionNVX -> CuFunctionNVX -> Bool) -> Eq CuFunctionNVX
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CuFunctionNVX -> CuFunctionNVX -> Bool
== :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c/= :: CuFunctionNVX -> CuFunctionNVX -> Bool
/= :: CuFunctionNVX -> CuFunctionNVX -> Bool
Eq, Eq CuFunctionNVX
Eq CuFunctionNVX =>
(CuFunctionNVX -> CuFunctionNVX -> Ordering)
-> (CuFunctionNVX -> CuFunctionNVX -> Bool)
-> (CuFunctionNVX -> CuFunctionNVX -> Bool)
-> (CuFunctionNVX -> CuFunctionNVX -> Bool)
-> (CuFunctionNVX -> CuFunctionNVX -> Bool)
-> (CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX)
-> (CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX)
-> Ord CuFunctionNVX
CuFunctionNVX -> CuFunctionNVX -> Bool
CuFunctionNVX -> CuFunctionNVX -> Ordering
CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
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
$ccompare :: CuFunctionNVX -> CuFunctionNVX -> Ordering
compare :: CuFunctionNVX -> CuFunctionNVX -> Ordering
$c< :: CuFunctionNVX -> CuFunctionNVX -> Bool
< :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c<= :: CuFunctionNVX -> CuFunctionNVX -> Bool
<= :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c> :: CuFunctionNVX -> CuFunctionNVX -> Bool
> :: CuFunctionNVX -> CuFunctionNVX -> Bool
$c>= :: CuFunctionNVX -> CuFunctionNVX -> Bool
>= :: CuFunctionNVX -> CuFunctionNVX -> Bool
$cmax :: CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
max :: CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
$cmin :: CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
min :: CuFunctionNVX -> CuFunctionNVX -> CuFunctionNVX
Ord, Ptr CuFunctionNVX -> IO CuFunctionNVX
Ptr CuFunctionNVX -> Int -> IO CuFunctionNVX
Ptr CuFunctionNVX -> Int -> CuFunctionNVX -> IO ()
Ptr CuFunctionNVX -> CuFunctionNVX -> IO ()
CuFunctionNVX -> Int
(CuFunctionNVX -> Int)
-> (CuFunctionNVX -> Int)
-> (Ptr CuFunctionNVX -> Int -> IO CuFunctionNVX)
-> (Ptr CuFunctionNVX -> Int -> CuFunctionNVX -> IO ())
-> (forall b. Ptr b -> Int -> IO CuFunctionNVX)
-> (forall b. Ptr b -> Int -> CuFunctionNVX -> IO ())
-> (Ptr CuFunctionNVX -> IO CuFunctionNVX)
-> (Ptr CuFunctionNVX -> CuFunctionNVX -> IO ())
-> Storable CuFunctionNVX
forall b. Ptr b -> Int -> IO CuFunctionNVX
forall b. Ptr b -> Int -> CuFunctionNVX -> 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
$csizeOf :: CuFunctionNVX -> Int
sizeOf :: CuFunctionNVX -> Int
$calignment :: CuFunctionNVX -> Int
alignment :: CuFunctionNVX -> Int
$cpeekElemOff :: Ptr CuFunctionNVX -> Int -> IO CuFunctionNVX
peekElemOff :: Ptr CuFunctionNVX -> Int -> IO CuFunctionNVX
$cpokeElemOff :: Ptr CuFunctionNVX -> Int -> CuFunctionNVX -> IO ()
pokeElemOff :: Ptr CuFunctionNVX -> Int -> CuFunctionNVX -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CuFunctionNVX
peekByteOff :: forall b. Ptr b -> Int -> IO CuFunctionNVX
$cpokeByteOff :: forall b. Ptr b -> Int -> CuFunctionNVX -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> CuFunctionNVX -> IO ()
$cpeek :: Ptr CuFunctionNVX -> IO CuFunctionNVX
peek :: Ptr CuFunctionNVX -> IO CuFunctionNVX
$cpoke :: Ptr CuFunctionNVX -> CuFunctionNVX -> IO ()
poke :: Ptr CuFunctionNVX -> CuFunctionNVX -> IO ()
Storable, CuFunctionNVX
CuFunctionNVX -> Zero CuFunctionNVX
forall a. a -> Zero a
$czero :: CuFunctionNVX
zero :: CuFunctionNVX
Zero)
  deriving anyclass (Eq CuFunctionNVX
Zero CuFunctionNVX
(Eq CuFunctionNVX, Zero CuFunctionNVX) => IsHandle CuFunctionNVX
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType CuFunctionNVX where
  objectTypeAndHandle :: CuFunctionNVX -> (ObjectType, Word64)
objectTypeAndHandle (CuFunctionNVX Word64
h) = (ObjectType
OBJECT_TYPE_CU_FUNCTION_NVX, Word64
h)
instance Show CuFunctionNVX where
  showsPrec :: Int -> CuFunctionNVX -> ShowS
showsPrec Int
p (CuFunctionNVX Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"CuFunctionNVX 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkOpticalFlowSessionNV - Opaque handle to an optical flow session object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_optical_flow VK_NV_optical_flow>,
-- 'Vulkan.Extensions.VK_NV_optical_flow.bindOpticalFlowSessionImageNV',
-- 'Vulkan.Extensions.VK_NV_optical_flow.cmdOpticalFlowExecuteNV',
-- 'Vulkan.Extensions.VK_NV_optical_flow.createOpticalFlowSessionNV',
-- 'Vulkan.Extensions.VK_NV_optical_flow.destroyOpticalFlowSessionNV'
newtype OpticalFlowSessionNV = OpticalFlowSessionNV Word64
  deriving newtype (OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
(OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool)
-> (OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool)
-> Eq OpticalFlowSessionNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
== :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c/= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
/= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
Eq, Eq OpticalFlowSessionNV
Eq OpticalFlowSessionNV =>
(OpticalFlowSessionNV -> OpticalFlowSessionNV -> Ordering)
-> (OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool)
-> (OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool)
-> (OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool)
-> (OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool)
-> (OpticalFlowSessionNV
    -> OpticalFlowSessionNV -> OpticalFlowSessionNV)
-> (OpticalFlowSessionNV
    -> OpticalFlowSessionNV -> OpticalFlowSessionNV)
-> Ord OpticalFlowSessionNV
OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
OpticalFlowSessionNV -> OpticalFlowSessionNV -> Ordering
OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
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
$ccompare :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Ordering
compare :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Ordering
$c< :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
< :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c<= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
<= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c> :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
> :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$c>= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
>= :: OpticalFlowSessionNV -> OpticalFlowSessionNV -> Bool
$cmax :: OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
max :: OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
$cmin :: OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
min :: OpticalFlowSessionNV
-> OpticalFlowSessionNV -> OpticalFlowSessionNV
Ord, Ptr OpticalFlowSessionNV -> IO OpticalFlowSessionNV
Ptr OpticalFlowSessionNV -> Int -> IO OpticalFlowSessionNV
Ptr OpticalFlowSessionNV -> Int -> OpticalFlowSessionNV -> IO ()
Ptr OpticalFlowSessionNV -> OpticalFlowSessionNV -> IO ()
OpticalFlowSessionNV -> Int
(OpticalFlowSessionNV -> Int)
-> (OpticalFlowSessionNV -> Int)
-> (Ptr OpticalFlowSessionNV -> Int -> IO OpticalFlowSessionNV)
-> (Ptr OpticalFlowSessionNV
    -> Int -> OpticalFlowSessionNV -> IO ())
-> (forall b. Ptr b -> Int -> IO OpticalFlowSessionNV)
-> (forall b. Ptr b -> Int -> OpticalFlowSessionNV -> IO ())
-> (Ptr OpticalFlowSessionNV -> IO OpticalFlowSessionNV)
-> (Ptr OpticalFlowSessionNV -> OpticalFlowSessionNV -> IO ())
-> Storable OpticalFlowSessionNV
forall b. Ptr b -> Int -> IO OpticalFlowSessionNV
forall b. Ptr b -> Int -> OpticalFlowSessionNV -> 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
$csizeOf :: OpticalFlowSessionNV -> Int
sizeOf :: OpticalFlowSessionNV -> Int
$calignment :: OpticalFlowSessionNV -> Int
alignment :: OpticalFlowSessionNV -> Int
$cpeekElemOff :: Ptr OpticalFlowSessionNV -> Int -> IO OpticalFlowSessionNV
peekElemOff :: Ptr OpticalFlowSessionNV -> Int -> IO OpticalFlowSessionNV
$cpokeElemOff :: Ptr OpticalFlowSessionNV -> Int -> OpticalFlowSessionNV -> IO ()
pokeElemOff :: Ptr OpticalFlowSessionNV -> Int -> OpticalFlowSessionNV -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO OpticalFlowSessionNV
peekByteOff :: forall b. Ptr b -> Int -> IO OpticalFlowSessionNV
$cpokeByteOff :: forall b. Ptr b -> Int -> OpticalFlowSessionNV -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> OpticalFlowSessionNV -> IO ()
$cpeek :: Ptr OpticalFlowSessionNV -> IO OpticalFlowSessionNV
peek :: Ptr OpticalFlowSessionNV -> IO OpticalFlowSessionNV
$cpoke :: Ptr OpticalFlowSessionNV -> OpticalFlowSessionNV -> IO ()
poke :: Ptr OpticalFlowSessionNV -> OpticalFlowSessionNV -> IO ()
Storable, OpticalFlowSessionNV
OpticalFlowSessionNV -> Zero OpticalFlowSessionNV
forall a. a -> Zero a
$czero :: OpticalFlowSessionNV
zero :: OpticalFlowSessionNV
Zero)
  deriving anyclass (Eq OpticalFlowSessionNV
Zero OpticalFlowSessionNV
(Eq OpticalFlowSessionNV, Zero OpticalFlowSessionNV) =>
IsHandle OpticalFlowSessionNV
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType OpticalFlowSessionNV where
  objectTypeAndHandle :: OpticalFlowSessionNV -> (ObjectType, Word64)
objectTypeAndHandle (OpticalFlowSessionNV Word64
h) = ( ObjectType
OBJECT_TYPE_OPTICAL_FLOW_SESSION_NV
                                                 , Word64
h )
instance Show OpticalFlowSessionNV where
  showsPrec :: Int -> OpticalFlowSessionNV -> ShowS
showsPrec Int
p (OpticalFlowSessionNV Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"OpticalFlowSessionNV 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkMicromapEXT - Opaque handle to a micromap object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Extensions.VK_NV_displacement_micromap.AccelerationStructureTrianglesDisplacementMicromapNV',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.AccelerationStructureTrianglesOpacityMicromapEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.CopyMemoryToMicromapInfoEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.CopyMicromapInfoEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.CopyMicromapToMemoryInfoEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.MicromapBuildInfoEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.cmdWriteMicromapsPropertiesEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.createMicromapEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.destroyMicromapEXT',
-- 'Vulkan.Extensions.VK_EXT_opacity_micromap.writeMicromapsPropertiesEXT'
newtype MicromapEXT = MicromapEXT Word64
  deriving newtype (MicromapEXT -> MicromapEXT -> Bool
(MicromapEXT -> MicromapEXT -> Bool)
-> (MicromapEXT -> MicromapEXT -> Bool) -> Eq MicromapEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MicromapEXT -> MicromapEXT -> Bool
== :: MicromapEXT -> MicromapEXT -> Bool
$c/= :: MicromapEXT -> MicromapEXT -> Bool
/= :: MicromapEXT -> MicromapEXT -> Bool
Eq, Eq MicromapEXT
Eq MicromapEXT =>
(MicromapEXT -> MicromapEXT -> Ordering)
-> (MicromapEXT -> MicromapEXT -> Bool)
-> (MicromapEXT -> MicromapEXT -> Bool)
-> (MicromapEXT -> MicromapEXT -> Bool)
-> (MicromapEXT -> MicromapEXT -> Bool)
-> (MicromapEXT -> MicromapEXT -> MicromapEXT)
-> (MicromapEXT -> MicromapEXT -> MicromapEXT)
-> Ord MicromapEXT
MicromapEXT -> MicromapEXT -> Bool
MicromapEXT -> MicromapEXT -> Ordering
MicromapEXT -> MicromapEXT -> MicromapEXT
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
$ccompare :: MicromapEXT -> MicromapEXT -> Ordering
compare :: MicromapEXT -> MicromapEXT -> Ordering
$c< :: MicromapEXT -> MicromapEXT -> Bool
< :: MicromapEXT -> MicromapEXT -> Bool
$c<= :: MicromapEXT -> MicromapEXT -> Bool
<= :: MicromapEXT -> MicromapEXT -> Bool
$c> :: MicromapEXT -> MicromapEXT -> Bool
> :: MicromapEXT -> MicromapEXT -> Bool
$c>= :: MicromapEXT -> MicromapEXT -> Bool
>= :: MicromapEXT -> MicromapEXT -> Bool
$cmax :: MicromapEXT -> MicromapEXT -> MicromapEXT
max :: MicromapEXT -> MicromapEXT -> MicromapEXT
$cmin :: MicromapEXT -> MicromapEXT -> MicromapEXT
min :: MicromapEXT -> MicromapEXT -> MicromapEXT
Ord, Ptr MicromapEXT -> IO MicromapEXT
Ptr MicromapEXT -> Int -> IO MicromapEXT
Ptr MicromapEXT -> Int -> MicromapEXT -> IO ()
Ptr MicromapEXT -> MicromapEXT -> IO ()
MicromapEXT -> Int
(MicromapEXT -> Int)
-> (MicromapEXT -> Int)
-> (Ptr MicromapEXT -> Int -> IO MicromapEXT)
-> (Ptr MicromapEXT -> Int -> MicromapEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO MicromapEXT)
-> (forall b. Ptr b -> Int -> MicromapEXT -> IO ())
-> (Ptr MicromapEXT -> IO MicromapEXT)
-> (Ptr MicromapEXT -> MicromapEXT -> IO ())
-> Storable MicromapEXT
forall b. Ptr b -> Int -> IO MicromapEXT
forall b. Ptr b -> Int -> MicromapEXT -> 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
$csizeOf :: MicromapEXT -> Int
sizeOf :: MicromapEXT -> Int
$calignment :: MicromapEXT -> Int
alignment :: MicromapEXT -> Int
$cpeekElemOff :: Ptr MicromapEXT -> Int -> IO MicromapEXT
peekElemOff :: Ptr MicromapEXT -> Int -> IO MicromapEXT
$cpokeElemOff :: Ptr MicromapEXT -> Int -> MicromapEXT -> IO ()
pokeElemOff :: Ptr MicromapEXT -> Int -> MicromapEXT -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MicromapEXT
peekByteOff :: forall b. Ptr b -> Int -> IO MicromapEXT
$cpokeByteOff :: forall b. Ptr b -> Int -> MicromapEXT -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> MicromapEXT -> IO ()
$cpeek :: Ptr MicromapEXT -> IO MicromapEXT
peek :: Ptr MicromapEXT -> IO MicromapEXT
$cpoke :: Ptr MicromapEXT -> MicromapEXT -> IO ()
poke :: Ptr MicromapEXT -> MicromapEXT -> IO ()
Storable, MicromapEXT
MicromapEXT -> Zero MicromapEXT
forall a. a -> Zero a
$czero :: MicromapEXT
zero :: MicromapEXT
Zero)
  deriving anyclass (Eq MicromapEXT
Zero MicromapEXT
(Eq MicromapEXT, Zero MicromapEXT) => IsHandle MicromapEXT
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType MicromapEXT where
  objectTypeAndHandle :: MicromapEXT -> (ObjectType, Word64)
objectTypeAndHandle (MicromapEXT Word64
h) = (ObjectType
OBJECT_TYPE_MICROMAP_EXT, Word64
h)
instance Show MicromapEXT where
  showsPrec :: Int -> MicromapEXT -> ShowS
showsPrec Int
p (MicromapEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"MicromapEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkShaderEXT - Opaque handle to a shader object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_shader_object VK_EXT_shader_object>,
-- 'Vulkan.Extensions.VK_EXT_shader_object.cmdBindShadersEXT',
-- 'Vulkan.Extensions.VK_EXT_shader_object.createShadersEXT',
-- 'Vulkan.Extensions.VK_EXT_shader_object.destroyShaderEXT',
-- 'Vulkan.Extensions.VK_EXT_shader_object.getShaderBinaryDataEXT'
newtype ShaderEXT = ShaderEXT Word64
  deriving newtype (ShaderEXT -> ShaderEXT -> Bool
(ShaderEXT -> ShaderEXT -> Bool)
-> (ShaderEXT -> ShaderEXT -> Bool) -> Eq ShaderEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ShaderEXT -> ShaderEXT -> Bool
== :: ShaderEXT -> ShaderEXT -> Bool
$c/= :: ShaderEXT -> ShaderEXT -> Bool
/= :: ShaderEXT -> ShaderEXT -> Bool
Eq, Eq ShaderEXT
Eq ShaderEXT =>
(ShaderEXT -> ShaderEXT -> Ordering)
-> (ShaderEXT -> ShaderEXT -> Bool)
-> (ShaderEXT -> ShaderEXT -> Bool)
-> (ShaderEXT -> ShaderEXT -> Bool)
-> (ShaderEXT -> ShaderEXT -> Bool)
-> (ShaderEXT -> ShaderEXT -> ShaderEXT)
-> (ShaderEXT -> ShaderEXT -> ShaderEXT)
-> Ord ShaderEXT
ShaderEXT -> ShaderEXT -> Bool
ShaderEXT -> ShaderEXT -> Ordering
ShaderEXT -> ShaderEXT -> ShaderEXT
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
$ccompare :: ShaderEXT -> ShaderEXT -> Ordering
compare :: ShaderEXT -> ShaderEXT -> Ordering
$c< :: ShaderEXT -> ShaderEXT -> Bool
< :: ShaderEXT -> ShaderEXT -> Bool
$c<= :: ShaderEXT -> ShaderEXT -> Bool
<= :: ShaderEXT -> ShaderEXT -> Bool
$c> :: ShaderEXT -> ShaderEXT -> Bool
> :: ShaderEXT -> ShaderEXT -> Bool
$c>= :: ShaderEXT -> ShaderEXT -> Bool
>= :: ShaderEXT -> ShaderEXT -> Bool
$cmax :: ShaderEXT -> ShaderEXT -> ShaderEXT
max :: ShaderEXT -> ShaderEXT -> ShaderEXT
$cmin :: ShaderEXT -> ShaderEXT -> ShaderEXT
min :: ShaderEXT -> ShaderEXT -> ShaderEXT
Ord, Ptr ShaderEXT -> IO ShaderEXT
Ptr ShaderEXT -> Int -> IO ShaderEXT
Ptr ShaderEXT -> Int -> ShaderEXT -> IO ()
Ptr ShaderEXT -> ShaderEXT -> IO ()
ShaderEXT -> Int
(ShaderEXT -> Int)
-> (ShaderEXT -> Int)
-> (Ptr ShaderEXT -> Int -> IO ShaderEXT)
-> (Ptr ShaderEXT -> Int -> ShaderEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO ShaderEXT)
-> (forall b. Ptr b -> Int -> ShaderEXT -> IO ())
-> (Ptr ShaderEXT -> IO ShaderEXT)
-> (Ptr ShaderEXT -> ShaderEXT -> IO ())
-> Storable ShaderEXT
forall b. Ptr b -> Int -> IO ShaderEXT
forall b. Ptr b -> Int -> ShaderEXT -> 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
$csizeOf :: ShaderEXT -> Int
sizeOf :: ShaderEXT -> Int
$calignment :: ShaderEXT -> Int
alignment :: ShaderEXT -> Int
$cpeekElemOff :: Ptr ShaderEXT -> Int -> IO ShaderEXT
peekElemOff :: Ptr ShaderEXT -> Int -> IO ShaderEXT
$cpokeElemOff :: Ptr ShaderEXT -> Int -> ShaderEXT -> IO ()
pokeElemOff :: Ptr ShaderEXT -> Int -> ShaderEXT -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ShaderEXT
peekByteOff :: forall b. Ptr b -> Int -> IO ShaderEXT
$cpokeByteOff :: forall b. Ptr b -> Int -> ShaderEXT -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> ShaderEXT -> IO ()
$cpeek :: Ptr ShaderEXT -> IO ShaderEXT
peek :: Ptr ShaderEXT -> IO ShaderEXT
$cpoke :: Ptr ShaderEXT -> ShaderEXT -> IO ()
poke :: Ptr ShaderEXT -> ShaderEXT -> IO ()
Storable, ShaderEXT
ShaderEXT -> Zero ShaderEXT
forall a. a -> Zero a
$czero :: ShaderEXT
zero :: ShaderEXT
Zero)
  deriving anyclass (Eq ShaderEXT
Zero ShaderEXT
(Eq ShaderEXT, Zero ShaderEXT) => IsHandle ShaderEXT
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType ShaderEXT where
  objectTypeAndHandle :: ShaderEXT -> (ObjectType, Word64)
objectTypeAndHandle (ShaderEXT Word64
h) = (ObjectType
OBJECT_TYPE_SHADER_EXT, Word64
h)
instance Show ShaderEXT where
  showsPrec :: Int -> ShaderEXT -> ShowS
showsPrec Int
p (ShaderEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"ShaderEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkDisplayKHR - Opaque handle to a display object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_display VK_KHR_display>,
-- 'Vulkan.Extensions.VK_KHR_display.DisplayPlanePropertiesKHR',
-- 'Vulkan.Extensions.VK_KHR_display.DisplayPropertiesKHR',
-- 'Vulkan.Extensions.VK_EXT_acquire_drm_display.acquireDrmDisplayEXT',
-- 'Vulkan.Extensions.VK_NV_acquire_winrt_display.acquireWinrtDisplayNV',
-- 'Vulkan.Extensions.VK_EXT_acquire_xlib_display.acquireXlibDisplayEXT',
-- 'Vulkan.Extensions.VK_KHR_display.createDisplayModeKHR',
-- 'Vulkan.Extensions.VK_EXT_display_control.displayPowerControlEXT',
-- 'Vulkan.Extensions.VK_KHR_get_display_properties2.getDisplayModeProperties2KHR',
-- 'Vulkan.Extensions.VK_KHR_display.getDisplayModePropertiesKHR',
-- 'Vulkan.Extensions.VK_KHR_display.getDisplayPlaneSupportedDisplaysKHR',
-- 'Vulkan.Extensions.VK_EXT_acquire_drm_display.getDrmDisplayEXT',
-- 'Vulkan.Extensions.VK_EXT_acquire_xlib_display.getRandROutputDisplayEXT',
-- 'Vulkan.Extensions.VK_NV_acquire_winrt_display.getWinrtDisplayNV',
-- 'Vulkan.Extensions.VK_EXT_display_control.registerDisplayEventEXT',
-- 'Vulkan.Extensions.VK_EXT_direct_mode_display.releaseDisplayEXT'
newtype DisplayKHR = DisplayKHR Word64
  deriving newtype (DisplayKHR -> DisplayKHR -> Bool
(DisplayKHR -> DisplayKHR -> Bool)
-> (DisplayKHR -> DisplayKHR -> Bool) -> Eq DisplayKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisplayKHR -> DisplayKHR -> Bool
== :: DisplayKHR -> DisplayKHR -> Bool
$c/= :: DisplayKHR -> DisplayKHR -> Bool
/= :: DisplayKHR -> DisplayKHR -> Bool
Eq, Eq DisplayKHR
Eq DisplayKHR =>
(DisplayKHR -> DisplayKHR -> Ordering)
-> (DisplayKHR -> DisplayKHR -> Bool)
-> (DisplayKHR -> DisplayKHR -> Bool)
-> (DisplayKHR -> DisplayKHR -> Bool)
-> (DisplayKHR -> DisplayKHR -> Bool)
-> (DisplayKHR -> DisplayKHR -> DisplayKHR)
-> (DisplayKHR -> DisplayKHR -> DisplayKHR)
-> Ord DisplayKHR
DisplayKHR -> DisplayKHR -> Bool
DisplayKHR -> DisplayKHR -> Ordering
DisplayKHR -> DisplayKHR -> DisplayKHR
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
$ccompare :: DisplayKHR -> DisplayKHR -> Ordering
compare :: DisplayKHR -> DisplayKHR -> Ordering
$c< :: DisplayKHR -> DisplayKHR -> Bool
< :: DisplayKHR -> DisplayKHR -> Bool
$c<= :: DisplayKHR -> DisplayKHR -> Bool
<= :: DisplayKHR -> DisplayKHR -> Bool
$c> :: DisplayKHR -> DisplayKHR -> Bool
> :: DisplayKHR -> DisplayKHR -> Bool
$c>= :: DisplayKHR -> DisplayKHR -> Bool
>= :: DisplayKHR -> DisplayKHR -> Bool
$cmax :: DisplayKHR -> DisplayKHR -> DisplayKHR
max :: DisplayKHR -> DisplayKHR -> DisplayKHR
$cmin :: DisplayKHR -> DisplayKHR -> DisplayKHR
min :: DisplayKHR -> DisplayKHR -> DisplayKHR
Ord, Ptr DisplayKHR -> IO DisplayKHR
Ptr DisplayKHR -> Int -> IO DisplayKHR
Ptr DisplayKHR -> Int -> DisplayKHR -> IO ()
Ptr DisplayKHR -> DisplayKHR -> IO ()
DisplayKHR -> Int
(DisplayKHR -> Int)
-> (DisplayKHR -> Int)
-> (Ptr DisplayKHR -> Int -> IO DisplayKHR)
-> (Ptr DisplayKHR -> Int -> DisplayKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO DisplayKHR)
-> (forall b. Ptr b -> Int -> DisplayKHR -> IO ())
-> (Ptr DisplayKHR -> IO DisplayKHR)
-> (Ptr DisplayKHR -> DisplayKHR -> IO ())
-> Storable DisplayKHR
forall b. Ptr b -> Int -> IO DisplayKHR
forall b. Ptr b -> Int -> DisplayKHR -> 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
$csizeOf :: DisplayKHR -> Int
sizeOf :: DisplayKHR -> Int
$calignment :: DisplayKHR -> Int
alignment :: DisplayKHR -> Int
$cpeekElemOff :: Ptr DisplayKHR -> Int -> IO DisplayKHR
peekElemOff :: Ptr DisplayKHR -> Int -> IO DisplayKHR
$cpokeElemOff :: Ptr DisplayKHR -> Int -> DisplayKHR -> IO ()
pokeElemOff :: Ptr DisplayKHR -> Int -> DisplayKHR -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DisplayKHR
peekByteOff :: forall b. Ptr b -> Int -> IO DisplayKHR
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayKHR -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> DisplayKHR -> IO ()
$cpeek :: Ptr DisplayKHR -> IO DisplayKHR
peek :: Ptr DisplayKHR -> IO DisplayKHR
$cpoke :: Ptr DisplayKHR -> DisplayKHR -> IO ()
poke :: Ptr DisplayKHR -> DisplayKHR -> IO ()
Storable, DisplayKHR
DisplayKHR -> Zero DisplayKHR
forall a. a -> Zero a
$czero :: DisplayKHR
zero :: DisplayKHR
Zero)
  deriving anyclass (Eq DisplayKHR
Zero DisplayKHR
(Eq DisplayKHR, Zero DisplayKHR) => IsHandle DisplayKHR
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType DisplayKHR where
  objectTypeAndHandle :: DisplayKHR -> (ObjectType, Word64)
objectTypeAndHandle (DisplayKHR Word64
h) = (ObjectType
OBJECT_TYPE_DISPLAY_KHR, Word64
h)
instance Show DisplayKHR where
  showsPrec :: Int -> DisplayKHR -> ShowS
showsPrec Int
p (DisplayKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DisplayKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkDisplayModeKHR - Opaque handle to a display mode object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_display VK_KHR_display>,
-- 'Vulkan.Extensions.VK_KHR_display.DisplayModePropertiesKHR',
-- 'Vulkan.Extensions.VK_KHR_get_display_properties2.DisplayPlaneInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_display.DisplaySurfaceCreateInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_display.createDisplayModeKHR',
-- 'Vulkan.Extensions.VK_KHR_display.getDisplayPlaneCapabilitiesKHR'
newtype DisplayModeKHR = DisplayModeKHR Word64
  deriving newtype (DisplayModeKHR -> DisplayModeKHR -> Bool
(DisplayModeKHR -> DisplayModeKHR -> Bool)
-> (DisplayModeKHR -> DisplayModeKHR -> Bool) -> Eq DisplayModeKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DisplayModeKHR -> DisplayModeKHR -> Bool
== :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c/= :: DisplayModeKHR -> DisplayModeKHR -> Bool
/= :: DisplayModeKHR -> DisplayModeKHR -> Bool
Eq, Eq DisplayModeKHR
Eq DisplayModeKHR =>
(DisplayModeKHR -> DisplayModeKHR -> Ordering)
-> (DisplayModeKHR -> DisplayModeKHR -> Bool)
-> (DisplayModeKHR -> DisplayModeKHR -> Bool)
-> (DisplayModeKHR -> DisplayModeKHR -> Bool)
-> (DisplayModeKHR -> DisplayModeKHR -> Bool)
-> (DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR)
-> (DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR)
-> Ord DisplayModeKHR
DisplayModeKHR -> DisplayModeKHR -> Bool
DisplayModeKHR -> DisplayModeKHR -> Ordering
DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
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
$ccompare :: DisplayModeKHR -> DisplayModeKHR -> Ordering
compare :: DisplayModeKHR -> DisplayModeKHR -> Ordering
$c< :: DisplayModeKHR -> DisplayModeKHR -> Bool
< :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c<= :: DisplayModeKHR -> DisplayModeKHR -> Bool
<= :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c> :: DisplayModeKHR -> DisplayModeKHR -> Bool
> :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c>= :: DisplayModeKHR -> DisplayModeKHR -> Bool
>= :: DisplayModeKHR -> DisplayModeKHR -> Bool
$cmax :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
max :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
$cmin :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
min :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
Ord, Ptr DisplayModeKHR -> IO DisplayModeKHR
Ptr DisplayModeKHR -> Int -> IO DisplayModeKHR
Ptr DisplayModeKHR -> Int -> DisplayModeKHR -> IO ()
Ptr DisplayModeKHR -> DisplayModeKHR -> IO ()
DisplayModeKHR -> Int
(DisplayModeKHR -> Int)
-> (DisplayModeKHR -> Int)
-> (Ptr DisplayModeKHR -> Int -> IO DisplayModeKHR)
-> (Ptr DisplayModeKHR -> Int -> DisplayModeKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO DisplayModeKHR)
-> (forall b. Ptr b -> Int -> DisplayModeKHR -> IO ())
-> (Ptr DisplayModeKHR -> IO DisplayModeKHR)
-> (Ptr DisplayModeKHR -> DisplayModeKHR -> IO ())
-> Storable DisplayModeKHR
forall b. Ptr b -> Int -> IO DisplayModeKHR
forall b. Ptr b -> Int -> DisplayModeKHR -> 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
$csizeOf :: DisplayModeKHR -> Int
sizeOf :: DisplayModeKHR -> Int
$calignment :: DisplayModeKHR -> Int
alignment :: DisplayModeKHR -> Int
$cpeekElemOff :: Ptr DisplayModeKHR -> Int -> IO DisplayModeKHR
peekElemOff :: Ptr DisplayModeKHR -> Int -> IO DisplayModeKHR
$cpokeElemOff :: Ptr DisplayModeKHR -> Int -> DisplayModeKHR -> IO ()
pokeElemOff :: Ptr DisplayModeKHR -> Int -> DisplayModeKHR -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DisplayModeKHR
peekByteOff :: forall b. Ptr b -> Int -> IO DisplayModeKHR
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayModeKHR -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> DisplayModeKHR -> IO ()
$cpeek :: Ptr DisplayModeKHR -> IO DisplayModeKHR
peek :: Ptr DisplayModeKHR -> IO DisplayModeKHR
$cpoke :: Ptr DisplayModeKHR -> DisplayModeKHR -> IO ()
poke :: Ptr DisplayModeKHR -> DisplayModeKHR -> IO ()
Storable, DisplayModeKHR
DisplayModeKHR -> Zero DisplayModeKHR
forall a. a -> Zero a
$czero :: DisplayModeKHR
zero :: DisplayModeKHR
Zero)
  deriving anyclass (Eq DisplayModeKHR
Zero DisplayModeKHR
(Eq DisplayModeKHR, Zero DisplayModeKHR) => IsHandle DisplayModeKHR
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType DisplayModeKHR where
  objectTypeAndHandle :: DisplayModeKHR -> (ObjectType, Word64)
objectTypeAndHandle (DisplayModeKHR Word64
h) = (ObjectType
OBJECT_TYPE_DISPLAY_MODE_KHR, Word64
h)
instance Show DisplayModeKHR where
  showsPrec :: Int -> DisplayModeKHR -> ShowS
showsPrec Int
p (DisplayModeKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DisplayModeKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkSurfaceKHR - Opaque handle to a surface object
--
-- = Description
--
-- The @VK_KHR_surface@ extension declares the 'SurfaceKHR' object, and
-- provides a function for destroying 'SurfaceKHR' objects. Separate
-- platform-specific extensions each provide a function for creating a
-- 'SurfaceKHR' object for the respective platform. From the application’s
-- perspective this is an opaque handle, just like the handles of other
-- Vulkan objects.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_surface VK_KHR_surface>,
-- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.PhysicalDeviceSurfaceInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.SwapchainCreateInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_android_surface.createAndroidSurfaceKHR',
-- 'Vulkan.Extensions.VK_EXT_directfb_surface.createDirectFBSurfaceEXT',
-- 'Vulkan.Extensions.VK_KHR_display.createDisplayPlaneSurfaceKHR',
-- 'Vulkan.Extensions.VK_EXT_headless_surface.createHeadlessSurfaceEXT',
-- 'Vulkan.Extensions.VK_MVK_ios_surface.createIOSSurfaceMVK',
-- 'Vulkan.Extensions.VK_FUCHSIA_imagepipe_surface.createImagePipeSurfaceFUCHSIA',
-- 'Vulkan.Extensions.VK_MVK_macos_surface.createMacOSSurfaceMVK',
-- 'Vulkan.Extensions.VK_EXT_metal_surface.createMetalSurfaceEXT',
-- 'Vulkan.Extensions.VK_QNX_screen_surface.createScreenSurfaceQNX',
-- 'Vulkan.Extensions.VK_GGP_stream_descriptor_surface.createStreamDescriptorSurfaceGGP',
-- 'Vulkan.Extensions.VK_NN_vi_surface.createViSurfaceNN',
-- 'Vulkan.Extensions.VK_KHR_wayland_surface.createWaylandSurfaceKHR',
-- 'Vulkan.Extensions.VK_KHR_win32_surface.createWin32SurfaceKHR',
-- 'Vulkan.Extensions.VK_KHR_xcb_surface.createXcbSurfaceKHR',
-- 'Vulkan.Extensions.VK_KHR_xlib_surface.createXlibSurfaceKHR',
-- 'Vulkan.Extensions.VK_KHR_surface.destroySurfaceKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.getDeviceGroupSurfacePresentModesKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.getPhysicalDevicePresentRectanglesKHR',
-- 'Vulkan.Extensions.VK_EXT_display_surface_counter.getPhysicalDeviceSurfaceCapabilities2EXT',
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR',
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceFormatsKHR',
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfacePresentModesKHR',
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceSupportKHR'
newtype SurfaceKHR = SurfaceKHR Word64
  deriving newtype (SurfaceKHR -> SurfaceKHR -> Bool
(SurfaceKHR -> SurfaceKHR -> Bool)
-> (SurfaceKHR -> SurfaceKHR -> Bool) -> Eq SurfaceKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SurfaceKHR -> SurfaceKHR -> Bool
== :: SurfaceKHR -> SurfaceKHR -> Bool
$c/= :: SurfaceKHR -> SurfaceKHR -> Bool
/= :: SurfaceKHR -> SurfaceKHR -> Bool
Eq, Eq SurfaceKHR
Eq SurfaceKHR =>
(SurfaceKHR -> SurfaceKHR -> Ordering)
-> (SurfaceKHR -> SurfaceKHR -> Bool)
-> (SurfaceKHR -> SurfaceKHR -> Bool)
-> (SurfaceKHR -> SurfaceKHR -> Bool)
-> (SurfaceKHR -> SurfaceKHR -> Bool)
-> (SurfaceKHR -> SurfaceKHR -> SurfaceKHR)
-> (SurfaceKHR -> SurfaceKHR -> SurfaceKHR)
-> Ord SurfaceKHR
SurfaceKHR -> SurfaceKHR -> Bool
SurfaceKHR -> SurfaceKHR -> Ordering
SurfaceKHR -> SurfaceKHR -> SurfaceKHR
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
$ccompare :: SurfaceKHR -> SurfaceKHR -> Ordering
compare :: SurfaceKHR -> SurfaceKHR -> Ordering
$c< :: SurfaceKHR -> SurfaceKHR -> Bool
< :: SurfaceKHR -> SurfaceKHR -> Bool
$c<= :: SurfaceKHR -> SurfaceKHR -> Bool
<= :: SurfaceKHR -> SurfaceKHR -> Bool
$c> :: SurfaceKHR -> SurfaceKHR -> Bool
> :: SurfaceKHR -> SurfaceKHR -> Bool
$c>= :: SurfaceKHR -> SurfaceKHR -> Bool
>= :: SurfaceKHR -> SurfaceKHR -> Bool
$cmax :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
max :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
$cmin :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
min :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
Ord, Ptr SurfaceKHR -> IO SurfaceKHR
Ptr SurfaceKHR -> Int -> IO SurfaceKHR
Ptr SurfaceKHR -> Int -> SurfaceKHR -> IO ()
Ptr SurfaceKHR -> SurfaceKHR -> IO ()
SurfaceKHR -> Int
(SurfaceKHR -> Int)
-> (SurfaceKHR -> Int)
-> (Ptr SurfaceKHR -> Int -> IO SurfaceKHR)
-> (Ptr SurfaceKHR -> Int -> SurfaceKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO SurfaceKHR)
-> (forall b. Ptr b -> Int -> SurfaceKHR -> IO ())
-> (Ptr SurfaceKHR -> IO SurfaceKHR)
-> (Ptr SurfaceKHR -> SurfaceKHR -> IO ())
-> Storable SurfaceKHR
forall b. Ptr b -> Int -> IO SurfaceKHR
forall b. Ptr b -> Int -> SurfaceKHR -> 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
$csizeOf :: SurfaceKHR -> Int
sizeOf :: SurfaceKHR -> Int
$calignment :: SurfaceKHR -> Int
alignment :: SurfaceKHR -> Int
$cpeekElemOff :: Ptr SurfaceKHR -> Int -> IO SurfaceKHR
peekElemOff :: Ptr SurfaceKHR -> Int -> IO SurfaceKHR
$cpokeElemOff :: Ptr SurfaceKHR -> Int -> SurfaceKHR -> IO ()
pokeElemOff :: Ptr SurfaceKHR -> Int -> SurfaceKHR -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SurfaceKHR
peekByteOff :: forall b. Ptr b -> Int -> IO SurfaceKHR
$cpokeByteOff :: forall b. Ptr b -> Int -> SurfaceKHR -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> SurfaceKHR -> IO ()
$cpeek :: Ptr SurfaceKHR -> IO SurfaceKHR
peek :: Ptr SurfaceKHR -> IO SurfaceKHR
$cpoke :: Ptr SurfaceKHR -> SurfaceKHR -> IO ()
poke :: Ptr SurfaceKHR -> SurfaceKHR -> IO ()
Storable, SurfaceKHR
SurfaceKHR -> Zero SurfaceKHR
forall a. a -> Zero a
$czero :: SurfaceKHR
zero :: SurfaceKHR
Zero)
  deriving anyclass (Eq SurfaceKHR
Zero SurfaceKHR
(Eq SurfaceKHR, Zero SurfaceKHR) => IsHandle SurfaceKHR
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType SurfaceKHR where
  objectTypeAndHandle :: SurfaceKHR -> (ObjectType, Word64)
objectTypeAndHandle (SurfaceKHR Word64
h) = (ObjectType
OBJECT_TYPE_SURFACE_KHR, Word64
h)
instance Show SurfaceKHR where
  showsPrec :: Int -> SurfaceKHR -> ShowS
showsPrec Int
p (SurfaceKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"SurfaceKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkSwapchainKHR - Opaque handle to a swapchain object
--
-- = Description
--
-- A swapchain is an abstraction for an array of presentable images that
-- are associated with a surface. The presentable images are represented by
-- 'Vulkan.Core10.Handles.Image' objects created by the platform. One image
-- (which /can/ be an array image for multiview\/stereoscopic-3D surfaces)
-- is displayed at a time, but multiple images /can/ be queued for
-- presentation. An application renders to the image, and then queues the
-- image for presentation to the surface.
--
-- A native window /cannot/ be associated with more than one non-retired
-- swapchain at a time. Further, swapchains /cannot/ be created for native
-- windows that have a non-Vulkan graphics API surface associated with
-- them.
--
-- Note
--
-- The presentation engine is an abstraction for the platform’s compositor
-- or display engine.
--
-- The presentation engine /may/ be synchronous or asynchronous with
-- respect to the application and\/or logical device.
--
-- Some implementations /may/ use the device’s graphics queue or dedicated
-- presentation hardware to perform presentation.
--
-- The presentable images of a swapchain are owned by the presentation
-- engine. An application /can/ acquire use of a presentable image from the
-- presentation engine. Use of a presentable image /must/ occur only after
-- the image is returned by
-- 'Vulkan.Extensions.VK_KHR_swapchain.acquireNextImageKHR', and before it
-- is released by 'Vulkan.Extensions.VK_KHR_swapchain.queuePresentKHR'.
-- This includes transitioning the image layout and rendering commands.
--
-- An application /can/ acquire use of a presentable image with
-- 'Vulkan.Extensions.VK_KHR_swapchain.acquireNextImageKHR'. After
-- acquiring a presentable image and before modifying it, the application
-- /must/ use a synchronization primitive to ensure that the presentation
-- engine has finished reading from the image. The application /can/ then
-- transition the image’s layout, queue rendering commands to it, etc.
-- Finally, the application presents the image with
-- 'Vulkan.Extensions.VK_KHR_swapchain.queuePresentKHR', which releases the
-- acquisition of the image. The application /can/ also release the
-- acquisition of the image through
-- 'Vulkan.Extensions.VK_EXT_swapchain_maintenance1.releaseSwapchainImagesEXT',
-- if the image is not in use by the device, and skip the present
-- operation.
--
-- The presentation engine controls the order in which presentable images
-- are acquired for use by the application.
--
-- Note
--
-- This allows the platform to handle situations which require out-of-order
-- return of images after presentation. At the same time, it allows the
-- application to generate command buffers referencing all of the images in
-- the swapchain at initialization time, rather than in its main loop.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_KHR_swapchain VK_KHR_swapchain>,
-- 'Vulkan.Extensions.VK_KHR_swapchain.AcquireNextImageInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.BindImageMemorySwapchainInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.ImageSwapchainCreateInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.PresentInfoKHR',
-- 'Vulkan.Extensions.VK_EXT_swapchain_maintenance1.ReleaseSwapchainImagesInfoEXT',
-- 'Vulkan.Extensions.VK_KHR_swapchain.SwapchainCreateInfoKHR',
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.acquireFullScreenExclusiveModeEXT',
-- 'Vulkan.Extensions.VK_KHR_swapchain.acquireNextImageKHR',
-- 'Vulkan.Extensions.VK_KHR_display_swapchain.createSharedSwapchainsKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.createSwapchainKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.destroySwapchainKHR',
-- 'Vulkan.Extensions.VK_NV_low_latency2.getLatencyTimingsNV',
-- 'Vulkan.Extensions.VK_GOOGLE_display_timing.getPastPresentationTimingGOOGLE',
-- 'Vulkan.Extensions.VK_GOOGLE_display_timing.getRefreshCycleDurationGOOGLE',
-- 'Vulkan.Extensions.VK_EXT_display_control.getSwapchainCounterEXT',
-- 'Vulkan.Extensions.VK_KHR_swapchain.getSwapchainImagesKHR',
-- 'Vulkan.Extensions.VK_KHR_shared_presentable_image.getSwapchainStatusKHR',
-- 'Vulkan.Extensions.VK_NV_low_latency2.latencySleepNV',
-- 'Vulkan.Extensions.VK_KHR_swapchain.queuePresentKHR',
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.releaseFullScreenExclusiveModeEXT',
-- 'Vulkan.Extensions.VK_EXT_hdr_metadata.setHdrMetadataEXT',
-- 'Vulkan.Extensions.VK_NV_low_latency2.setLatencyMarkerNV',
-- 'Vulkan.Extensions.VK_NV_low_latency2.setLatencySleepModeNV',
-- 'Vulkan.Extensions.VK_AMD_display_native_hdr.setLocalDimmingAMD',
-- 'Vulkan.Extensions.VK_KHR_present_wait.waitForPresentKHR'
newtype SwapchainKHR = SwapchainKHR Word64
  deriving newtype (SwapchainKHR -> SwapchainKHR -> Bool
(SwapchainKHR -> SwapchainKHR -> Bool)
-> (SwapchainKHR -> SwapchainKHR -> Bool) -> Eq SwapchainKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SwapchainKHR -> SwapchainKHR -> Bool
== :: SwapchainKHR -> SwapchainKHR -> Bool
$c/= :: SwapchainKHR -> SwapchainKHR -> Bool
/= :: SwapchainKHR -> SwapchainKHR -> Bool
Eq, Eq SwapchainKHR
Eq SwapchainKHR =>
(SwapchainKHR -> SwapchainKHR -> Ordering)
-> (SwapchainKHR -> SwapchainKHR -> Bool)
-> (SwapchainKHR -> SwapchainKHR -> Bool)
-> (SwapchainKHR -> SwapchainKHR -> Bool)
-> (SwapchainKHR -> SwapchainKHR -> Bool)
-> (SwapchainKHR -> SwapchainKHR -> SwapchainKHR)
-> (SwapchainKHR -> SwapchainKHR -> SwapchainKHR)
-> Ord SwapchainKHR
SwapchainKHR -> SwapchainKHR -> Bool
SwapchainKHR -> SwapchainKHR -> Ordering
SwapchainKHR -> SwapchainKHR -> SwapchainKHR
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
$ccompare :: SwapchainKHR -> SwapchainKHR -> Ordering
compare :: SwapchainKHR -> SwapchainKHR -> Ordering
$c< :: SwapchainKHR -> SwapchainKHR -> Bool
< :: SwapchainKHR -> SwapchainKHR -> Bool
$c<= :: SwapchainKHR -> SwapchainKHR -> Bool
<= :: SwapchainKHR -> SwapchainKHR -> Bool
$c> :: SwapchainKHR -> SwapchainKHR -> Bool
> :: SwapchainKHR -> SwapchainKHR -> Bool
$c>= :: SwapchainKHR -> SwapchainKHR -> Bool
>= :: SwapchainKHR -> SwapchainKHR -> Bool
$cmax :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
max :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
$cmin :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
min :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
Ord, Ptr SwapchainKHR -> IO SwapchainKHR
Ptr SwapchainKHR -> Int -> IO SwapchainKHR
Ptr SwapchainKHR -> Int -> SwapchainKHR -> IO ()
Ptr SwapchainKHR -> SwapchainKHR -> IO ()
SwapchainKHR -> Int
(SwapchainKHR -> Int)
-> (SwapchainKHR -> Int)
-> (Ptr SwapchainKHR -> Int -> IO SwapchainKHR)
-> (Ptr SwapchainKHR -> Int -> SwapchainKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO SwapchainKHR)
-> (forall b. Ptr b -> Int -> SwapchainKHR -> IO ())
-> (Ptr SwapchainKHR -> IO SwapchainKHR)
-> (Ptr SwapchainKHR -> SwapchainKHR -> IO ())
-> Storable SwapchainKHR
forall b. Ptr b -> Int -> IO SwapchainKHR
forall b. Ptr b -> Int -> SwapchainKHR -> 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
$csizeOf :: SwapchainKHR -> Int
sizeOf :: SwapchainKHR -> Int
$calignment :: SwapchainKHR -> Int
alignment :: SwapchainKHR -> Int
$cpeekElemOff :: Ptr SwapchainKHR -> Int -> IO SwapchainKHR
peekElemOff :: Ptr SwapchainKHR -> Int -> IO SwapchainKHR
$cpokeElemOff :: Ptr SwapchainKHR -> Int -> SwapchainKHR -> IO ()
pokeElemOff :: Ptr SwapchainKHR -> Int -> SwapchainKHR -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SwapchainKHR
peekByteOff :: forall b. Ptr b -> Int -> IO SwapchainKHR
$cpokeByteOff :: forall b. Ptr b -> Int -> SwapchainKHR -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> SwapchainKHR -> IO ()
$cpeek :: Ptr SwapchainKHR -> IO SwapchainKHR
peek :: Ptr SwapchainKHR -> IO SwapchainKHR
$cpoke :: Ptr SwapchainKHR -> SwapchainKHR -> IO ()
poke :: Ptr SwapchainKHR -> SwapchainKHR -> IO ()
Storable, SwapchainKHR
SwapchainKHR -> Zero SwapchainKHR
forall a. a -> Zero a
$czero :: SwapchainKHR
zero :: SwapchainKHR
Zero)
  deriving anyclass (Eq SwapchainKHR
Zero SwapchainKHR
(Eq SwapchainKHR, Zero SwapchainKHR) => IsHandle SwapchainKHR
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType SwapchainKHR where
  objectTypeAndHandle :: SwapchainKHR -> (ObjectType, Word64)
objectTypeAndHandle (SwapchainKHR Word64
h) = (ObjectType
OBJECT_TYPE_SWAPCHAIN_KHR, Word64
h)
instance Show SwapchainKHR where
  showsPrec :: Int -> SwapchainKHR -> ShowS
showsPrec Int
p (SwapchainKHR Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"SwapchainKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkDebugReportCallbackEXT - Opaque handle to a debug report callback
-- object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_report VK_EXT_debug_report>,
-- 'Vulkan.Extensions.VK_EXT_debug_report.createDebugReportCallbackEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_report.destroyDebugReportCallbackEXT'
newtype DebugReportCallbackEXT = DebugReportCallbackEXT Word64
  deriving newtype (DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
(DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool)
-> (DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool)
-> Eq DebugReportCallbackEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
== :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c/= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
/= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
Eq, Eq DebugReportCallbackEXT
Eq DebugReportCallbackEXT =>
(DebugReportCallbackEXT -> DebugReportCallbackEXT -> Ordering)
-> (DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool)
-> (DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool)
-> (DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool)
-> (DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool)
-> (DebugReportCallbackEXT
    -> DebugReportCallbackEXT -> DebugReportCallbackEXT)
-> (DebugReportCallbackEXT
    -> DebugReportCallbackEXT -> DebugReportCallbackEXT)
-> Ord DebugReportCallbackEXT
DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
DebugReportCallbackEXT -> DebugReportCallbackEXT -> Ordering
DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
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
$ccompare :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Ordering
compare :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Ordering
$c< :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
< :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c<= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
<= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c> :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
> :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c>= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
>= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$cmax :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
max :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
$cmin :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
min :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
Ord, Ptr DebugReportCallbackEXT -> IO DebugReportCallbackEXT
Ptr DebugReportCallbackEXT -> Int -> IO DebugReportCallbackEXT
Ptr DebugReportCallbackEXT
-> Int -> DebugReportCallbackEXT -> IO ()
Ptr DebugReportCallbackEXT -> DebugReportCallbackEXT -> IO ()
DebugReportCallbackEXT -> Int
(DebugReportCallbackEXT -> Int)
-> (DebugReportCallbackEXT -> Int)
-> (Ptr DebugReportCallbackEXT -> Int -> IO DebugReportCallbackEXT)
-> (Ptr DebugReportCallbackEXT
    -> Int -> DebugReportCallbackEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DebugReportCallbackEXT)
-> (forall b. Ptr b -> Int -> DebugReportCallbackEXT -> IO ())
-> (Ptr DebugReportCallbackEXT -> IO DebugReportCallbackEXT)
-> (Ptr DebugReportCallbackEXT -> DebugReportCallbackEXT -> IO ())
-> Storable DebugReportCallbackEXT
forall b. Ptr b -> Int -> IO DebugReportCallbackEXT
forall b. Ptr b -> Int -> DebugReportCallbackEXT -> 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
$csizeOf :: DebugReportCallbackEXT -> Int
sizeOf :: DebugReportCallbackEXT -> Int
$calignment :: DebugReportCallbackEXT -> Int
alignment :: DebugReportCallbackEXT -> Int
$cpeekElemOff :: Ptr DebugReportCallbackEXT -> Int -> IO DebugReportCallbackEXT
peekElemOff :: Ptr DebugReportCallbackEXT -> Int -> IO DebugReportCallbackEXT
$cpokeElemOff :: Ptr DebugReportCallbackEXT
-> Int -> DebugReportCallbackEXT -> IO ()
pokeElemOff :: Ptr DebugReportCallbackEXT
-> Int -> DebugReportCallbackEXT -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DebugReportCallbackEXT
peekByteOff :: forall b. Ptr b -> Int -> IO DebugReportCallbackEXT
$cpokeByteOff :: forall b. Ptr b -> Int -> DebugReportCallbackEXT -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> DebugReportCallbackEXT -> IO ()
$cpeek :: Ptr DebugReportCallbackEXT -> IO DebugReportCallbackEXT
peek :: Ptr DebugReportCallbackEXT -> IO DebugReportCallbackEXT
$cpoke :: Ptr DebugReportCallbackEXT -> DebugReportCallbackEXT -> IO ()
poke :: Ptr DebugReportCallbackEXT -> DebugReportCallbackEXT -> IO ()
Storable, DebugReportCallbackEXT
DebugReportCallbackEXT -> Zero DebugReportCallbackEXT
forall a. a -> Zero a
$czero :: DebugReportCallbackEXT
zero :: DebugReportCallbackEXT
Zero)
  deriving anyclass (Eq DebugReportCallbackEXT
Zero DebugReportCallbackEXT
(Eq DebugReportCallbackEXT, Zero DebugReportCallbackEXT) =>
IsHandle DebugReportCallbackEXT
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType DebugReportCallbackEXT where
  objectTypeAndHandle :: DebugReportCallbackEXT -> (ObjectType, Word64)
objectTypeAndHandle (DebugReportCallbackEXT Word64
h) = ( ObjectType
OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT
                                                   , Word64
h )
instance Show DebugReportCallbackEXT where
  showsPrec :: Int -> DebugReportCallbackEXT -> ShowS
showsPrec Int
p (DebugReportCallbackEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DebugReportCallbackEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkDebugUtilsMessengerEXT - Opaque handle to a debug messenger object
--
-- = Description
--
-- The debug messenger will provide detailed feedback on the application’s
-- use of Vulkan when events of interest occur. When an event of interest
-- does occur, the debug messenger will submit a debug message to the debug
-- callback that was provided during its creation. Additionally, the debug
-- messenger is responsible with filtering out debug messages that the
-- callback is not interested in and will only provide desired debug
-- messages.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_debug_utils VK_EXT_debug_utils>,
-- 'Vulkan.Extensions.VK_EXT_debug_utils.createDebugUtilsMessengerEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.destroyDebugUtilsMessengerEXT'
newtype DebugUtilsMessengerEXT = DebugUtilsMessengerEXT Word64
  deriving newtype (DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
(DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool)
-> (DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool)
-> Eq DebugUtilsMessengerEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
== :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c/= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
/= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
Eq, Eq DebugUtilsMessengerEXT
Eq DebugUtilsMessengerEXT =>
(DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Ordering)
-> (DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool)
-> (DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool)
-> (DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool)
-> (DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool)
-> (DebugUtilsMessengerEXT
    -> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT)
-> (DebugUtilsMessengerEXT
    -> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT)
-> Ord DebugUtilsMessengerEXT
DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Ordering
DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
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
$ccompare :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Ordering
compare :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Ordering
$c< :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
< :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c<= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
<= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c> :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
> :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c>= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
>= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$cmax :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
max :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
$cmin :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
min :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
Ord, Ptr DebugUtilsMessengerEXT -> IO DebugUtilsMessengerEXT
Ptr DebugUtilsMessengerEXT -> Int -> IO DebugUtilsMessengerEXT
Ptr DebugUtilsMessengerEXT
-> Int -> DebugUtilsMessengerEXT -> IO ()
Ptr DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> IO ()
DebugUtilsMessengerEXT -> Int
(DebugUtilsMessengerEXT -> Int)
-> (DebugUtilsMessengerEXT -> Int)
-> (Ptr DebugUtilsMessengerEXT -> Int -> IO DebugUtilsMessengerEXT)
-> (Ptr DebugUtilsMessengerEXT
    -> Int -> DebugUtilsMessengerEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DebugUtilsMessengerEXT)
-> (forall b. Ptr b -> Int -> DebugUtilsMessengerEXT -> IO ())
-> (Ptr DebugUtilsMessengerEXT -> IO DebugUtilsMessengerEXT)
-> (Ptr DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> IO ())
-> Storable DebugUtilsMessengerEXT
forall b. Ptr b -> Int -> IO DebugUtilsMessengerEXT
forall b. Ptr b -> Int -> DebugUtilsMessengerEXT -> 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
$csizeOf :: DebugUtilsMessengerEXT -> Int
sizeOf :: DebugUtilsMessengerEXT -> Int
$calignment :: DebugUtilsMessengerEXT -> Int
alignment :: DebugUtilsMessengerEXT -> Int
$cpeekElemOff :: Ptr DebugUtilsMessengerEXT -> Int -> IO DebugUtilsMessengerEXT
peekElemOff :: Ptr DebugUtilsMessengerEXT -> Int -> IO DebugUtilsMessengerEXT
$cpokeElemOff :: Ptr DebugUtilsMessengerEXT
-> Int -> DebugUtilsMessengerEXT -> IO ()
pokeElemOff :: Ptr DebugUtilsMessengerEXT
-> Int -> DebugUtilsMessengerEXT -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DebugUtilsMessengerEXT
peekByteOff :: forall b. Ptr b -> Int -> IO DebugUtilsMessengerEXT
$cpokeByteOff :: forall b. Ptr b -> Int -> DebugUtilsMessengerEXT -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> DebugUtilsMessengerEXT -> IO ()
$cpeek :: Ptr DebugUtilsMessengerEXT -> IO DebugUtilsMessengerEXT
peek :: Ptr DebugUtilsMessengerEXT -> IO DebugUtilsMessengerEXT
$cpoke :: Ptr DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> IO ()
poke :: Ptr DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> IO ()
Storable, DebugUtilsMessengerEXT
DebugUtilsMessengerEXT -> Zero DebugUtilsMessengerEXT
forall a. a -> Zero a
$czero :: DebugUtilsMessengerEXT
zero :: DebugUtilsMessengerEXT
Zero)
  deriving anyclass (Eq DebugUtilsMessengerEXT
Zero DebugUtilsMessengerEXT
(Eq DebugUtilsMessengerEXT, Zero DebugUtilsMessengerEXT) =>
IsHandle DebugUtilsMessengerEXT
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType DebugUtilsMessengerEXT where
  objectTypeAndHandle :: DebugUtilsMessengerEXT -> (ObjectType, Word64)
objectTypeAndHandle (DebugUtilsMessengerEXT Word64
h) = ( ObjectType
OBJECT_TYPE_DEBUG_UTILS_MESSENGER_EXT
                                                   , Word64
h )
instance Show DebugUtilsMessengerEXT where
  showsPrec :: Int -> DebugUtilsMessengerEXT -> ShowS
showsPrec Int
p (DebugUtilsMessengerEXT Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"DebugUtilsMessengerEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkCudaModuleNV - Opaque handle to a CUDA module object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_cuda_kernel_launch VK_NV_cuda_kernel_launch>,
-- 'Vulkan.Extensions.VK_NV_cuda_kernel_launch.CudaFunctionCreateInfoNV',
-- 'Vulkan.Extensions.VK_NV_cuda_kernel_launch.createCudaModuleNV',
-- 'Vulkan.Extensions.VK_NV_cuda_kernel_launch.destroyCudaModuleNV',
-- 'Vulkan.Extensions.VK_NV_cuda_kernel_launch.getCudaModuleCacheNV'
newtype CudaModuleNV = CudaModuleNV Word64
  deriving newtype (CudaModuleNV -> CudaModuleNV -> Bool
(CudaModuleNV -> CudaModuleNV -> Bool)
-> (CudaModuleNV -> CudaModuleNV -> Bool) -> Eq CudaModuleNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CudaModuleNV -> CudaModuleNV -> Bool
== :: CudaModuleNV -> CudaModuleNV -> Bool
$c/= :: CudaModuleNV -> CudaModuleNV -> Bool
/= :: CudaModuleNV -> CudaModuleNV -> Bool
Eq, Eq CudaModuleNV
Eq CudaModuleNV =>
(CudaModuleNV -> CudaModuleNV -> Ordering)
-> (CudaModuleNV -> CudaModuleNV -> Bool)
-> (CudaModuleNV -> CudaModuleNV -> Bool)
-> (CudaModuleNV -> CudaModuleNV -> Bool)
-> (CudaModuleNV -> CudaModuleNV -> Bool)
-> (CudaModuleNV -> CudaModuleNV -> CudaModuleNV)
-> (CudaModuleNV -> CudaModuleNV -> CudaModuleNV)
-> Ord CudaModuleNV
CudaModuleNV -> CudaModuleNV -> Bool
CudaModuleNV -> CudaModuleNV -> Ordering
CudaModuleNV -> CudaModuleNV -> CudaModuleNV
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
$ccompare :: CudaModuleNV -> CudaModuleNV -> Ordering
compare :: CudaModuleNV -> CudaModuleNV -> Ordering
$c< :: CudaModuleNV -> CudaModuleNV -> Bool
< :: CudaModuleNV -> CudaModuleNV -> Bool
$c<= :: CudaModuleNV -> CudaModuleNV -> Bool
<= :: CudaModuleNV -> CudaModuleNV -> Bool
$c> :: CudaModuleNV -> CudaModuleNV -> Bool
> :: CudaModuleNV -> CudaModuleNV -> Bool
$c>= :: CudaModuleNV -> CudaModuleNV -> Bool
>= :: CudaModuleNV -> CudaModuleNV -> Bool
$cmax :: CudaModuleNV -> CudaModuleNV -> CudaModuleNV
max :: CudaModuleNV -> CudaModuleNV -> CudaModuleNV
$cmin :: CudaModuleNV -> CudaModuleNV -> CudaModuleNV
min :: CudaModuleNV -> CudaModuleNV -> CudaModuleNV
Ord, Ptr CudaModuleNV -> IO CudaModuleNV
Ptr CudaModuleNV -> Int -> IO CudaModuleNV
Ptr CudaModuleNV -> Int -> CudaModuleNV -> IO ()
Ptr CudaModuleNV -> CudaModuleNV -> IO ()
CudaModuleNV -> Int
(CudaModuleNV -> Int)
-> (CudaModuleNV -> Int)
-> (Ptr CudaModuleNV -> Int -> IO CudaModuleNV)
-> (Ptr CudaModuleNV -> Int -> CudaModuleNV -> IO ())
-> (forall b. Ptr b -> Int -> IO CudaModuleNV)
-> (forall b. Ptr b -> Int -> CudaModuleNV -> IO ())
-> (Ptr CudaModuleNV -> IO CudaModuleNV)
-> (Ptr CudaModuleNV -> CudaModuleNV -> IO ())
-> Storable CudaModuleNV
forall b. Ptr b -> Int -> IO CudaModuleNV
forall b. Ptr b -> Int -> CudaModuleNV -> 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
$csizeOf :: CudaModuleNV -> Int
sizeOf :: CudaModuleNV -> Int
$calignment :: CudaModuleNV -> Int
alignment :: CudaModuleNV -> Int
$cpeekElemOff :: Ptr CudaModuleNV -> Int -> IO CudaModuleNV
peekElemOff :: Ptr CudaModuleNV -> Int -> IO CudaModuleNV
$cpokeElemOff :: Ptr CudaModuleNV -> Int -> CudaModuleNV -> IO ()
pokeElemOff :: Ptr CudaModuleNV -> Int -> CudaModuleNV -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CudaModuleNV
peekByteOff :: forall b. Ptr b -> Int -> IO CudaModuleNV
$cpokeByteOff :: forall b. Ptr b -> Int -> CudaModuleNV -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> CudaModuleNV -> IO ()
$cpeek :: Ptr CudaModuleNV -> IO CudaModuleNV
peek :: Ptr CudaModuleNV -> IO CudaModuleNV
$cpoke :: Ptr CudaModuleNV -> CudaModuleNV -> IO ()
poke :: Ptr CudaModuleNV -> CudaModuleNV -> IO ()
Storable, CudaModuleNV
CudaModuleNV -> Zero CudaModuleNV
forall a. a -> Zero a
$czero :: CudaModuleNV
zero :: CudaModuleNV
Zero)
  deriving anyclass (Eq CudaModuleNV
Zero CudaModuleNV
(Eq CudaModuleNV, Zero CudaModuleNV) => IsHandle CudaModuleNV
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType CudaModuleNV where
  objectTypeAndHandle :: CudaModuleNV -> (ObjectType, Word64)
objectTypeAndHandle (CudaModuleNV Word64
h) = (ObjectType
OBJECT_TYPE_CUDA_MODULE_NV, Word64
h)
instance Show CudaModuleNV where
  showsPrec :: Int -> CudaModuleNV -> ShowS
showsPrec Int
p (CudaModuleNV Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"CudaModuleNV 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)


-- | VkCudaFunctionNV - Opaque handle to a CUDA function object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_NV_cuda_kernel_launch VK_NV_cuda_kernel_launch>,
-- 'Vulkan.Extensions.VK_NV_cuda_kernel_launch.CudaLaunchInfoNV',
-- 'Vulkan.Extensions.VK_NV_cuda_kernel_launch.createCudaFunctionNV',
-- 'Vulkan.Extensions.VK_NV_cuda_kernel_launch.destroyCudaFunctionNV'
newtype CudaFunctionNV = CudaFunctionNV Word64
  deriving newtype (CudaFunctionNV -> CudaFunctionNV -> Bool
(CudaFunctionNV -> CudaFunctionNV -> Bool)
-> (CudaFunctionNV -> CudaFunctionNV -> Bool) -> Eq CudaFunctionNV
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CudaFunctionNV -> CudaFunctionNV -> Bool
== :: CudaFunctionNV -> CudaFunctionNV -> Bool
$c/= :: CudaFunctionNV -> CudaFunctionNV -> Bool
/= :: CudaFunctionNV -> CudaFunctionNV -> Bool
Eq, Eq CudaFunctionNV
Eq CudaFunctionNV =>
(CudaFunctionNV -> CudaFunctionNV -> Ordering)
-> (CudaFunctionNV -> CudaFunctionNV -> Bool)
-> (CudaFunctionNV -> CudaFunctionNV -> Bool)
-> (CudaFunctionNV -> CudaFunctionNV -> Bool)
-> (CudaFunctionNV -> CudaFunctionNV -> Bool)
-> (CudaFunctionNV -> CudaFunctionNV -> CudaFunctionNV)
-> (CudaFunctionNV -> CudaFunctionNV -> CudaFunctionNV)
-> Ord CudaFunctionNV
CudaFunctionNV -> CudaFunctionNV -> Bool
CudaFunctionNV -> CudaFunctionNV -> Ordering
CudaFunctionNV -> CudaFunctionNV -> CudaFunctionNV
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
$ccompare :: CudaFunctionNV -> CudaFunctionNV -> Ordering
compare :: CudaFunctionNV -> CudaFunctionNV -> Ordering
$c< :: CudaFunctionNV -> CudaFunctionNV -> Bool
< :: CudaFunctionNV -> CudaFunctionNV -> Bool
$c<= :: CudaFunctionNV -> CudaFunctionNV -> Bool
<= :: CudaFunctionNV -> CudaFunctionNV -> Bool
$c> :: CudaFunctionNV -> CudaFunctionNV -> Bool
> :: CudaFunctionNV -> CudaFunctionNV -> Bool
$c>= :: CudaFunctionNV -> CudaFunctionNV -> Bool
>= :: CudaFunctionNV -> CudaFunctionNV -> Bool
$cmax :: CudaFunctionNV -> CudaFunctionNV -> CudaFunctionNV
max :: CudaFunctionNV -> CudaFunctionNV -> CudaFunctionNV
$cmin :: CudaFunctionNV -> CudaFunctionNV -> CudaFunctionNV
min :: CudaFunctionNV -> CudaFunctionNV -> CudaFunctionNV
Ord, Ptr CudaFunctionNV -> IO CudaFunctionNV
Ptr CudaFunctionNV -> Int -> IO CudaFunctionNV
Ptr CudaFunctionNV -> Int -> CudaFunctionNV -> IO ()
Ptr CudaFunctionNV -> CudaFunctionNV -> IO ()
CudaFunctionNV -> Int
(CudaFunctionNV -> Int)
-> (CudaFunctionNV -> Int)
-> (Ptr CudaFunctionNV -> Int -> IO CudaFunctionNV)
-> (Ptr CudaFunctionNV -> Int -> CudaFunctionNV -> IO ())
-> (forall b. Ptr b -> Int -> IO CudaFunctionNV)
-> (forall b. Ptr b -> Int -> CudaFunctionNV -> IO ())
-> (Ptr CudaFunctionNV -> IO CudaFunctionNV)
-> (Ptr CudaFunctionNV -> CudaFunctionNV -> IO ())
-> Storable CudaFunctionNV
forall b. Ptr b -> Int -> IO CudaFunctionNV
forall b. Ptr b -> Int -> CudaFunctionNV -> 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
$csizeOf :: CudaFunctionNV -> Int
sizeOf :: CudaFunctionNV -> Int
$calignment :: CudaFunctionNV -> Int
alignment :: CudaFunctionNV -> Int
$cpeekElemOff :: Ptr CudaFunctionNV -> Int -> IO CudaFunctionNV
peekElemOff :: Ptr CudaFunctionNV -> Int -> IO CudaFunctionNV
$cpokeElemOff :: Ptr CudaFunctionNV -> Int -> CudaFunctionNV -> IO ()
pokeElemOff :: Ptr CudaFunctionNV -> Int -> CudaFunctionNV -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CudaFunctionNV
peekByteOff :: forall b. Ptr b -> Int -> IO CudaFunctionNV
$cpokeByteOff :: forall b. Ptr b -> Int -> CudaFunctionNV -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> CudaFunctionNV -> IO ()
$cpeek :: Ptr CudaFunctionNV -> IO CudaFunctionNV
peek :: Ptr CudaFunctionNV -> IO CudaFunctionNV
$cpoke :: Ptr CudaFunctionNV -> CudaFunctionNV -> IO ()
poke :: Ptr CudaFunctionNV -> CudaFunctionNV -> IO ()
Storable, CudaFunctionNV
CudaFunctionNV -> Zero CudaFunctionNV
forall a. a -> Zero a
$czero :: CudaFunctionNV
zero :: CudaFunctionNV
Zero)
  deriving anyclass (Eq CudaFunctionNV
Zero CudaFunctionNV
(Eq CudaFunctionNV, Zero CudaFunctionNV) => IsHandle CudaFunctionNV
forall a. (Eq a, Zero a) => IsHandle a
IsHandle)
instance HasObjectType CudaFunctionNV where
  objectTypeAndHandle :: CudaFunctionNV -> (ObjectType, Word64)
objectTypeAndHandle (CudaFunctionNV Word64
h) = (ObjectType
OBJECT_TYPE_CUDA_FUNCTION_NV, Word64
h)
instance Show CudaFunctionNV where
  showsPrec :: Int -> CudaFunctionNV -> ShowS
showsPrec Int
p (CudaFunctionNV Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
11) (String -> ShowS
showString String
"CudaFunctionNV 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. Integral a => a -> ShowS
showHex Word64
x)