{-# language CPP #-}
module Vulkan.Extensions.Handles  ( IndirectCommandsLayoutNV(..)
                                  , ValidationCacheEXT(..)
                                  , AccelerationStructureKHR(..)
                                  , PerformanceConfigurationINTEL(..)
                                  , DeferredOperationKHR(..)
                                  , PrivateDataSlotEXT(..)
                                  , DisplayKHR(..)
                                  , DisplayModeKHR(..)
                                  , SurfaceKHR(..)
                                  , SwapchainKHR(..)
                                  , DebugReportCallbackEXT(..)
                                  , DebugUtilsMessengerEXT(..)
                                  , Instance(..)
                                  , PhysicalDevice(..)
                                  , Device(..)
                                  , Queue(..)
                                  , CommandBuffer(..)
                                  , DeviceMemory(..)
                                  , CommandPool(..)
                                  , Buffer(..)
                                  , BufferView(..)
                                  , Image(..)
                                  , ImageView(..)
                                  , ShaderModule(..)
                                  , Pipeline(..)
                                  , PipelineLayout(..)
                                  , Sampler(..)
                                  , DescriptorSet(..)
                                  , DescriptorSetLayout(..)
                                  , Fence(..)
                                  , Semaphore(..)
                                  , QueryPool(..)
                                  , Framebuffer(..)
                                  , RenderPass(..)
                                  , PipelineCache(..)
                                  , DescriptorUpdateTemplate(..)
                                  , SamplerYcbcrConversion(..)
                                  ) where

import GHC.Show (showParen)
import Numeric (showHex)
import Foreign.Storable (Storable)
import Data.Word (Word64)
import Vulkan.Core10.APIConstants (HasObjectType(..))
import Vulkan.Core10.APIConstants (IsHandle)
import Vulkan.Zero (Zero)
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR))
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_PERFORMANCE_CONFIGURATION_INTEL))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_PRIVATE_DATA_SLOT_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 (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.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
--
-- '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
/= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c/= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
== :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$c== :: 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
min :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
$cmin :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
max :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
$cmax :: IndirectCommandsLayoutNV
-> IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV
>= :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Bool
$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
compare :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Ordering
$ccompare :: IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> Ordering
$cp1Ord :: Eq IndirectCommandsLayoutNV
Ord, Ptr b -> Int -> IO IndirectCommandsLayoutNV
Ptr b -> Int -> IndirectCommandsLayoutNV -> IO ()
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
poke :: Ptr IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> IO ()
$cpoke :: Ptr IndirectCommandsLayoutNV -> IndirectCommandsLayoutNV -> IO ()
peek :: Ptr IndirectCommandsLayoutNV -> IO IndirectCommandsLayoutNV
$cpeek :: Ptr IndirectCommandsLayoutNV -> IO IndirectCommandsLayoutNV
pokeByteOff :: Ptr b -> Int -> IndirectCommandsLayoutNV -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> IndirectCommandsLayoutNV -> IO ()
peekByteOff :: Ptr b -> Int -> IO IndirectCommandsLayoutNV
$cpeekByteOff :: forall b. Ptr b -> Int -> IO IndirectCommandsLayoutNV
pokeElemOff :: Ptr IndirectCommandsLayoutNV
-> Int -> IndirectCommandsLayoutNV -> IO ()
$cpokeElemOff :: Ptr IndirectCommandsLayoutNV
-> Int -> IndirectCommandsLayoutNV -> IO ()
peekElemOff :: Ptr IndirectCommandsLayoutNV -> Int -> IO IndirectCommandsLayoutNV
$cpeekElemOff :: Ptr IndirectCommandsLayoutNV -> Int -> IO IndirectCommandsLayoutNV
alignment :: IndirectCommandsLayoutNV -> Int
$calignment :: IndirectCommandsLayoutNV -> Int
sizeOf :: IndirectCommandsLayoutNV -> Int
$csizeOf :: IndirectCommandsLayoutNV -> Int
Storable, IndirectCommandsLayoutNV
IndirectCommandsLayoutNV -> Zero IndirectCommandsLayoutNV
forall a. a -> Zero a
zero :: IndirectCommandsLayoutNV
$czero :: IndirectCommandsLayoutNV
Zero)
  deriving anyclass (Eq IndirectCommandsLayoutNV
Zero IndirectCommandsLayoutNV
(Eq IndirectCommandsLayoutNV, Zero IndirectCommandsLayoutNV) =>
IsHandle IndirectCommandsLayoutNV
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero IndirectCommandsLayoutNV
$cp1IsHandle :: Eq IndirectCommandsLayoutNV
IsHandle)
instance HasObjectType IndirectCommandsLayoutNV where
  objectTypeAndHandle :: IndirectCommandsLayoutNV -> (ObjectType, Word64)
objectTypeAndHandle (IndirectCommandsLayoutNV h :: Word64
h) = (ObjectType
OBJECT_TYPE_INDIRECT_COMMANDS_LAYOUT_NV, Word64
h)
instance Show IndirectCommandsLayoutNV where
  showsPrec :: Int -> IndirectCommandsLayoutNV -> ShowS
showsPrec p :: Int
p (IndirectCommandsLayoutNV x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "IndirectCommandsLayoutNV 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)


-- | VkValidationCacheEXT - Opaque handle to a validation cache object
--
-- = See Also
--
-- '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
/= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c/= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
== :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$c== :: 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
min :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
$cmin :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
max :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
$cmax :: ValidationCacheEXT -> ValidationCacheEXT -> ValidationCacheEXT
>= :: ValidationCacheEXT -> ValidationCacheEXT -> Bool
$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
compare :: ValidationCacheEXT -> ValidationCacheEXT -> Ordering
$ccompare :: ValidationCacheEXT -> ValidationCacheEXT -> Ordering
$cp1Ord :: Eq ValidationCacheEXT
Ord, Ptr b -> Int -> IO ValidationCacheEXT
Ptr b -> Int -> ValidationCacheEXT -> IO ()
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
poke :: Ptr ValidationCacheEXT -> ValidationCacheEXT -> IO ()
$cpoke :: Ptr ValidationCacheEXT -> ValidationCacheEXT -> IO ()
peek :: Ptr ValidationCacheEXT -> IO ValidationCacheEXT
$cpeek :: Ptr ValidationCacheEXT -> IO ValidationCacheEXT
pokeByteOff :: Ptr b -> Int -> ValidationCacheEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ValidationCacheEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO ValidationCacheEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ValidationCacheEXT
pokeElemOff :: Ptr ValidationCacheEXT -> Int -> ValidationCacheEXT -> IO ()
$cpokeElemOff :: Ptr ValidationCacheEXT -> Int -> ValidationCacheEXT -> IO ()
peekElemOff :: Ptr ValidationCacheEXT -> Int -> IO ValidationCacheEXT
$cpeekElemOff :: Ptr ValidationCacheEXT -> Int -> IO ValidationCacheEXT
alignment :: ValidationCacheEXT -> Int
$calignment :: ValidationCacheEXT -> Int
sizeOf :: ValidationCacheEXT -> Int
$csizeOf :: ValidationCacheEXT -> Int
Storable, ValidationCacheEXT
ValidationCacheEXT -> Zero ValidationCacheEXT
forall a. a -> Zero a
zero :: ValidationCacheEXT
$czero :: ValidationCacheEXT
Zero)
  deriving anyclass (Eq ValidationCacheEXT
Zero ValidationCacheEXT
(Eq ValidationCacheEXT, Zero ValidationCacheEXT) =>
IsHandle ValidationCacheEXT
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero ValidationCacheEXT
$cp1IsHandle :: Eq ValidationCacheEXT
IsHandle)
instance HasObjectType ValidationCacheEXT where
  objectTypeAndHandle :: ValidationCacheEXT -> (ObjectType, Word64)
objectTypeAndHandle (ValidationCacheEXT h :: Word64
h) = (ObjectType
OBJECT_TYPE_VALIDATION_CACHE_EXT, Word64
h)
instance Show ValidationCacheEXT where
  showsPrec :: Int -> ValidationCacheEXT -> ShowS
showsPrec p :: Int
p (ValidationCacheEXT x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "ValidationCacheEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)


-- | VkAccelerationStructureKHR - Opaque handle to an acceleration structure
-- object
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.AccelerationStructureBuildGeometryInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.AccelerationStructureDeviceAddressInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.AccelerationStructureMemoryRequirementsInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.BindAccelerationStructureMemoryInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.CopyAccelerationStructureInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.CopyAccelerationStructureToMemoryInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.CopyMemoryToAccelerationStructureInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.WriteDescriptorSetAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdBuildAccelerationStructureNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdCopyAccelerationStructureNV',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdWriteAccelerationStructuresPropertiesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdWriteAccelerationStructuresPropertiesNV',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.createAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.destroyAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.destroyAccelerationStructureNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.getAccelerationStructureHandleNV',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.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
/= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c/= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
== :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$c== :: 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
min :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
$cmin :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
max :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
$cmax :: AccelerationStructureKHR
-> AccelerationStructureKHR -> AccelerationStructureKHR
>= :: AccelerationStructureKHR -> AccelerationStructureKHR -> Bool
$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
compare :: AccelerationStructureKHR -> AccelerationStructureKHR -> Ordering
$ccompare :: AccelerationStructureKHR -> AccelerationStructureKHR -> Ordering
$cp1Ord :: Eq AccelerationStructureKHR
Ord, Ptr b -> Int -> IO AccelerationStructureKHR
Ptr b -> Int -> AccelerationStructureKHR -> IO ()
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
poke :: Ptr AccelerationStructureKHR -> AccelerationStructureKHR -> IO ()
$cpoke :: Ptr AccelerationStructureKHR -> AccelerationStructureKHR -> IO ()
peek :: Ptr AccelerationStructureKHR -> IO AccelerationStructureKHR
$cpeek :: Ptr AccelerationStructureKHR -> IO AccelerationStructureKHR
pokeByteOff :: Ptr b -> Int -> AccelerationStructureKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO AccelerationStructureKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureKHR
pokeElemOff :: Ptr AccelerationStructureKHR
-> Int -> AccelerationStructureKHR -> IO ()
$cpokeElemOff :: Ptr AccelerationStructureKHR
-> Int -> AccelerationStructureKHR -> IO ()
peekElemOff :: Ptr AccelerationStructureKHR -> Int -> IO AccelerationStructureKHR
$cpeekElemOff :: Ptr AccelerationStructureKHR -> Int -> IO AccelerationStructureKHR
alignment :: AccelerationStructureKHR -> Int
$calignment :: AccelerationStructureKHR -> Int
sizeOf :: AccelerationStructureKHR -> Int
$csizeOf :: AccelerationStructureKHR -> Int
Storable, AccelerationStructureKHR
AccelerationStructureKHR -> Zero AccelerationStructureKHR
forall a. a -> Zero a
zero :: AccelerationStructureKHR
$czero :: AccelerationStructureKHR
Zero)
  deriving anyclass (Eq AccelerationStructureKHR
Zero AccelerationStructureKHR
(Eq AccelerationStructureKHR, Zero AccelerationStructureKHR) =>
IsHandle AccelerationStructureKHR
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero AccelerationStructureKHR
$cp1IsHandle :: Eq AccelerationStructureKHR
IsHandle)
instance HasObjectType AccelerationStructureKHR where
  objectTypeAndHandle :: AccelerationStructureKHR -> (ObjectType, Word64)
objectTypeAndHandle (AccelerationStructureKHR h :: Word64
h) = (ObjectType
OBJECT_TYPE_ACCELERATION_STRUCTURE_KHR, Word64
h)
instance Show AccelerationStructureKHR where
  showsPrec :: Int -> AccelerationStructureKHR -> ShowS
showsPrec p :: Int
p (AccelerationStructureKHR x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "AccelerationStructureKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)


-- | VkPerformanceConfigurationINTEL - Device configuration for performance
-- queries
--
-- = See Also
--
-- '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
/= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c/= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
== :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$c== :: 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
min :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
$cmin :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
max :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
$cmax :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> PerformanceConfigurationINTEL
>= :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Bool
$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
compare :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Ordering
$ccompare :: PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> Ordering
$cp1Ord :: Eq PerformanceConfigurationINTEL
Ord, Ptr b -> Int -> IO PerformanceConfigurationINTEL
Ptr b -> Int -> PerformanceConfigurationINTEL -> IO ()
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
poke :: Ptr PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> IO ()
$cpoke :: Ptr PerformanceConfigurationINTEL
-> PerformanceConfigurationINTEL -> IO ()
peek :: Ptr PerformanceConfigurationINTEL
-> IO PerformanceConfigurationINTEL
$cpeek :: Ptr PerformanceConfigurationINTEL
-> IO PerformanceConfigurationINTEL
pokeByteOff :: Ptr b -> Int -> PerformanceConfigurationINTEL -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PerformanceConfigurationINTEL -> IO ()
peekByteOff :: Ptr b -> Int -> IO PerformanceConfigurationINTEL
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PerformanceConfigurationINTEL
pokeElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> PerformanceConfigurationINTEL -> IO ()
$cpokeElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> PerformanceConfigurationINTEL -> IO ()
peekElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> IO PerformanceConfigurationINTEL
$cpeekElemOff :: Ptr PerformanceConfigurationINTEL
-> Int -> IO PerformanceConfigurationINTEL
alignment :: PerformanceConfigurationINTEL -> Int
$calignment :: PerformanceConfigurationINTEL -> Int
sizeOf :: PerformanceConfigurationINTEL -> Int
$csizeOf :: PerformanceConfigurationINTEL -> Int
Storable, PerformanceConfigurationINTEL
PerformanceConfigurationINTEL -> Zero PerformanceConfigurationINTEL
forall a. a -> Zero a
zero :: PerformanceConfigurationINTEL
$czero :: PerformanceConfigurationINTEL
Zero)
  deriving anyclass (Eq PerformanceConfigurationINTEL
Zero PerformanceConfigurationINTEL
(Eq PerformanceConfigurationINTEL,
 Zero PerformanceConfigurationINTEL) =>
IsHandle PerformanceConfigurationINTEL
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero PerformanceConfigurationINTEL
$cp1IsHandle :: Eq PerformanceConfigurationINTEL
IsHandle)
instance HasObjectType PerformanceConfigurationINTEL where
  objectTypeAndHandle :: PerformanceConfigurationINTEL -> (ObjectType, Word64)
objectTypeAndHandle (PerformanceConfigurationINTEL h :: Word64
h) = (ObjectType
OBJECT_TYPE_PERFORMANCE_CONFIGURATION_INTEL, Word64
h)
instance Show PerformanceConfigurationINTEL where
  showsPrec :: Int -> PerformanceConfigurationINTEL -> ShowS
showsPrec p :: Int
p (PerformanceConfigurationINTEL x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PerformanceConfigurationINTEL 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show 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
--
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.createDeferredOperationKHR',
-- '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
/= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c/= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
== :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$c== :: 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
min :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
$cmin :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
max :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
$cmax :: DeferredOperationKHR
-> DeferredOperationKHR -> DeferredOperationKHR
>= :: DeferredOperationKHR -> DeferredOperationKHR -> Bool
$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
compare :: DeferredOperationKHR -> DeferredOperationKHR -> Ordering
$ccompare :: DeferredOperationKHR -> DeferredOperationKHR -> Ordering
$cp1Ord :: Eq DeferredOperationKHR
Ord, Ptr b -> Int -> IO DeferredOperationKHR
Ptr b -> Int -> DeferredOperationKHR -> IO ()
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
poke :: Ptr DeferredOperationKHR -> DeferredOperationKHR -> IO ()
$cpoke :: Ptr DeferredOperationKHR -> DeferredOperationKHR -> IO ()
peek :: Ptr DeferredOperationKHR -> IO DeferredOperationKHR
$cpeek :: Ptr DeferredOperationKHR -> IO DeferredOperationKHR
pokeByteOff :: Ptr b -> Int -> DeferredOperationKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DeferredOperationKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO DeferredOperationKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DeferredOperationKHR
pokeElemOff :: Ptr DeferredOperationKHR -> Int -> DeferredOperationKHR -> IO ()
$cpokeElemOff :: Ptr DeferredOperationKHR -> Int -> DeferredOperationKHR -> IO ()
peekElemOff :: Ptr DeferredOperationKHR -> Int -> IO DeferredOperationKHR
$cpeekElemOff :: Ptr DeferredOperationKHR -> Int -> IO DeferredOperationKHR
alignment :: DeferredOperationKHR -> Int
$calignment :: DeferredOperationKHR -> Int
sizeOf :: DeferredOperationKHR -> Int
$csizeOf :: DeferredOperationKHR -> Int
Storable, DeferredOperationKHR
DeferredOperationKHR -> Zero DeferredOperationKHR
forall a. a -> Zero a
zero :: DeferredOperationKHR
$czero :: DeferredOperationKHR
Zero)
  deriving anyclass (Eq DeferredOperationKHR
Zero DeferredOperationKHR
(Eq DeferredOperationKHR, Zero DeferredOperationKHR) =>
IsHandle DeferredOperationKHR
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DeferredOperationKHR
$cp1IsHandle :: Eq DeferredOperationKHR
IsHandle)
instance HasObjectType DeferredOperationKHR where
  objectTypeAndHandle :: DeferredOperationKHR -> (ObjectType, Word64)
objectTypeAndHandle (DeferredOperationKHR h :: Word64
h) = (ObjectType
OBJECT_TYPE_DEFERRED_OPERATION_KHR, Word64
h)
instance Show DeferredOperationKHR where
  showsPrec :: Int -> DeferredOperationKHR -> ShowS
showsPrec p :: Int
p (DeferredOperationKHR x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DeferredOperationKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)


-- | VkPrivateDataSlotEXT - Opaque handle to a private data slot object
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_EXT_private_data.createPrivateDataSlotEXT',
-- 'Vulkan.Extensions.VK_EXT_private_data.destroyPrivateDataSlotEXT',
-- 'Vulkan.Extensions.VK_EXT_private_data.getPrivateDataEXT',
-- 'Vulkan.Extensions.VK_EXT_private_data.setPrivateDataEXT'
newtype PrivateDataSlotEXT = PrivateDataSlotEXT Word64
  deriving newtype (PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
(PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool)
-> (PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool)
-> Eq PrivateDataSlotEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
$c/= :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
== :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
$c== :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
Eq, Eq PrivateDataSlotEXT
Eq PrivateDataSlotEXT =>
(PrivateDataSlotEXT -> PrivateDataSlotEXT -> Ordering)
-> (PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool)
-> (PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool)
-> (PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool)
-> (PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool)
-> (PrivateDataSlotEXT -> PrivateDataSlotEXT -> PrivateDataSlotEXT)
-> (PrivateDataSlotEXT -> PrivateDataSlotEXT -> PrivateDataSlotEXT)
-> Ord PrivateDataSlotEXT
PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
PrivateDataSlotEXT -> PrivateDataSlotEXT -> Ordering
PrivateDataSlotEXT -> PrivateDataSlotEXT -> PrivateDataSlotEXT
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> PrivateDataSlotEXT
$cmin :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> PrivateDataSlotEXT
max :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> PrivateDataSlotEXT
$cmax :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> PrivateDataSlotEXT
>= :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
$c>= :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
> :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
$c> :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
<= :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
$c<= :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
< :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
$c< :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Bool
compare :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Ordering
$ccompare :: PrivateDataSlotEXT -> PrivateDataSlotEXT -> Ordering
$cp1Ord :: Eq PrivateDataSlotEXT
Ord, Ptr b -> Int -> IO PrivateDataSlotEXT
Ptr b -> Int -> PrivateDataSlotEXT -> IO ()
Ptr PrivateDataSlotEXT -> IO PrivateDataSlotEXT
Ptr PrivateDataSlotEXT -> Int -> IO PrivateDataSlotEXT
Ptr PrivateDataSlotEXT -> Int -> PrivateDataSlotEXT -> IO ()
Ptr PrivateDataSlotEXT -> PrivateDataSlotEXT -> IO ()
PrivateDataSlotEXT -> Int
(PrivateDataSlotEXT -> Int)
-> (PrivateDataSlotEXT -> Int)
-> (Ptr PrivateDataSlotEXT -> Int -> IO PrivateDataSlotEXT)
-> (Ptr PrivateDataSlotEXT -> Int -> PrivateDataSlotEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO PrivateDataSlotEXT)
-> (forall b. Ptr b -> Int -> PrivateDataSlotEXT -> IO ())
-> (Ptr PrivateDataSlotEXT -> IO PrivateDataSlotEXT)
-> (Ptr PrivateDataSlotEXT -> PrivateDataSlotEXT -> IO ())
-> Storable PrivateDataSlotEXT
forall b. Ptr b -> Int -> IO PrivateDataSlotEXT
forall b. Ptr b -> Int -> PrivateDataSlotEXT -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PrivateDataSlotEXT -> PrivateDataSlotEXT -> IO ()
$cpoke :: Ptr PrivateDataSlotEXT -> PrivateDataSlotEXT -> IO ()
peek :: Ptr PrivateDataSlotEXT -> IO PrivateDataSlotEXT
$cpeek :: Ptr PrivateDataSlotEXT -> IO PrivateDataSlotEXT
pokeByteOff :: Ptr b -> Int -> PrivateDataSlotEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PrivateDataSlotEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO PrivateDataSlotEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PrivateDataSlotEXT
pokeElemOff :: Ptr PrivateDataSlotEXT -> Int -> PrivateDataSlotEXT -> IO ()
$cpokeElemOff :: Ptr PrivateDataSlotEXT -> Int -> PrivateDataSlotEXT -> IO ()
peekElemOff :: Ptr PrivateDataSlotEXT -> Int -> IO PrivateDataSlotEXT
$cpeekElemOff :: Ptr PrivateDataSlotEXT -> Int -> IO PrivateDataSlotEXT
alignment :: PrivateDataSlotEXT -> Int
$calignment :: PrivateDataSlotEXT -> Int
sizeOf :: PrivateDataSlotEXT -> Int
$csizeOf :: PrivateDataSlotEXT -> Int
Storable, PrivateDataSlotEXT
PrivateDataSlotEXT -> Zero PrivateDataSlotEXT
forall a. a -> Zero a
zero :: PrivateDataSlotEXT
$czero :: PrivateDataSlotEXT
Zero)
  deriving anyclass (Eq PrivateDataSlotEXT
Zero PrivateDataSlotEXT
(Eq PrivateDataSlotEXT, Zero PrivateDataSlotEXT) =>
IsHandle PrivateDataSlotEXT
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero PrivateDataSlotEXT
$cp1IsHandle :: Eq PrivateDataSlotEXT
IsHandle)
instance HasObjectType PrivateDataSlotEXT where
  objectTypeAndHandle :: PrivateDataSlotEXT -> (ObjectType, Word64)
objectTypeAndHandle (PrivateDataSlotEXT h :: Word64
h) = (ObjectType
OBJECT_TYPE_PRIVATE_DATA_SLOT_EXT, Word64
h)
instance Show PrivateDataSlotEXT where
  showsPrec :: Int -> PrivateDataSlotEXT -> ShowS
showsPrec p :: Int
p (PrivateDataSlotEXT x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PrivateDataSlotEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)


-- | VkDisplayKHR - Opaque handle to a display object
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_display.DisplayPlanePropertiesKHR',
-- 'Vulkan.Extensions.VK_KHR_display.DisplayPropertiesKHR',
-- '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_xlib_display.getRandROutputDisplayEXT',
-- '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
/= :: DisplayKHR -> DisplayKHR -> Bool
$c/= :: DisplayKHR -> DisplayKHR -> Bool
== :: DisplayKHR -> DisplayKHR -> Bool
$c== :: 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
min :: DisplayKHR -> DisplayKHR -> DisplayKHR
$cmin :: DisplayKHR -> DisplayKHR -> DisplayKHR
max :: DisplayKHR -> DisplayKHR -> DisplayKHR
$cmax :: DisplayKHR -> DisplayKHR -> DisplayKHR
>= :: DisplayKHR -> DisplayKHR -> Bool
$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
compare :: DisplayKHR -> DisplayKHR -> Ordering
$ccompare :: DisplayKHR -> DisplayKHR -> Ordering
$cp1Ord :: Eq DisplayKHR
Ord, Ptr b -> Int -> IO DisplayKHR
Ptr b -> Int -> DisplayKHR -> IO ()
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
poke :: Ptr DisplayKHR -> DisplayKHR -> IO ()
$cpoke :: Ptr DisplayKHR -> DisplayKHR -> IO ()
peek :: Ptr DisplayKHR -> IO DisplayKHR
$cpeek :: Ptr DisplayKHR -> IO DisplayKHR
pokeByteOff :: Ptr b -> Int -> DisplayKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO DisplayKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DisplayKHR
pokeElemOff :: Ptr DisplayKHR -> Int -> DisplayKHR -> IO ()
$cpokeElemOff :: Ptr DisplayKHR -> Int -> DisplayKHR -> IO ()
peekElemOff :: Ptr DisplayKHR -> Int -> IO DisplayKHR
$cpeekElemOff :: Ptr DisplayKHR -> Int -> IO DisplayKHR
alignment :: DisplayKHR -> Int
$calignment :: DisplayKHR -> Int
sizeOf :: DisplayKHR -> Int
$csizeOf :: DisplayKHR -> Int
Storable, DisplayKHR
DisplayKHR -> Zero DisplayKHR
forall a. a -> Zero a
zero :: DisplayKHR
$czero :: DisplayKHR
Zero)
  deriving anyclass (Eq DisplayKHR
Zero DisplayKHR
(Eq DisplayKHR, Zero DisplayKHR) => IsHandle DisplayKHR
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DisplayKHR
$cp1IsHandle :: Eq DisplayKHR
IsHandle)
instance HasObjectType DisplayKHR where
  objectTypeAndHandle :: DisplayKHR -> (ObjectType, Word64)
objectTypeAndHandle (DisplayKHR h :: Word64
h) = (ObjectType
OBJECT_TYPE_DISPLAY_KHR, Word64
h)
instance Show DisplayKHR where
  showsPrec :: Int -> DisplayKHR -> ShowS
showsPrec p :: Int
p (DisplayKHR x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DisplayKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)


-- | VkDisplayModeKHR - Opaque handle to a display mode object
--
-- = See Also
--
-- '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
/= :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c/= :: DisplayModeKHR -> DisplayModeKHR -> Bool
== :: DisplayModeKHR -> DisplayModeKHR -> Bool
$c== :: 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
min :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
$cmin :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
max :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
$cmax :: DisplayModeKHR -> DisplayModeKHR -> DisplayModeKHR
>= :: DisplayModeKHR -> DisplayModeKHR -> Bool
$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
compare :: DisplayModeKHR -> DisplayModeKHR -> Ordering
$ccompare :: DisplayModeKHR -> DisplayModeKHR -> Ordering
$cp1Ord :: Eq DisplayModeKHR
Ord, Ptr b -> Int -> IO DisplayModeKHR
Ptr b -> Int -> DisplayModeKHR -> IO ()
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
poke :: Ptr DisplayModeKHR -> DisplayModeKHR -> IO ()
$cpoke :: Ptr DisplayModeKHR -> DisplayModeKHR -> IO ()
peek :: Ptr DisplayModeKHR -> IO DisplayModeKHR
$cpeek :: Ptr DisplayModeKHR -> IO DisplayModeKHR
pokeByteOff :: Ptr b -> Int -> DisplayModeKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DisplayModeKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO DisplayModeKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DisplayModeKHR
pokeElemOff :: Ptr DisplayModeKHR -> Int -> DisplayModeKHR -> IO ()
$cpokeElemOff :: Ptr DisplayModeKHR -> Int -> DisplayModeKHR -> IO ()
peekElemOff :: Ptr DisplayModeKHR -> Int -> IO DisplayModeKHR
$cpeekElemOff :: Ptr DisplayModeKHR -> Int -> IO DisplayModeKHR
alignment :: DisplayModeKHR -> Int
$calignment :: DisplayModeKHR -> Int
sizeOf :: DisplayModeKHR -> Int
$csizeOf :: DisplayModeKHR -> Int
Storable, DisplayModeKHR
DisplayModeKHR -> Zero DisplayModeKHR
forall a. a -> Zero a
zero :: DisplayModeKHR
$czero :: DisplayModeKHR
Zero)
  deriving anyclass (Eq DisplayModeKHR
Zero DisplayModeKHR
(Eq DisplayModeKHR, Zero DisplayModeKHR) => IsHandle DisplayModeKHR
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DisplayModeKHR
$cp1IsHandle :: Eq DisplayModeKHR
IsHandle)
instance HasObjectType DisplayModeKHR where
  objectTypeAndHandle :: DisplayModeKHR -> (ObjectType, Word64)
objectTypeAndHandle (DisplayModeKHR h :: Word64
h) = (ObjectType
OBJECT_TYPE_DISPLAY_MODE_KHR, Word64
h)
instance Show DisplayModeKHR where
  showsPrec :: Int -> DisplayModeKHR -> ShowS
showsPrec p :: Int
p (DisplayModeKHR x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DisplayModeKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show 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
--
-- '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_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
/= :: SurfaceKHR -> SurfaceKHR -> Bool
$c/= :: SurfaceKHR -> SurfaceKHR -> Bool
== :: SurfaceKHR -> SurfaceKHR -> Bool
$c== :: 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
min :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
$cmin :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
max :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
$cmax :: SurfaceKHR -> SurfaceKHR -> SurfaceKHR
>= :: SurfaceKHR -> SurfaceKHR -> Bool
$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
compare :: SurfaceKHR -> SurfaceKHR -> Ordering
$ccompare :: SurfaceKHR -> SurfaceKHR -> Ordering
$cp1Ord :: Eq SurfaceKHR
Ord, Ptr b -> Int -> IO SurfaceKHR
Ptr b -> Int -> SurfaceKHR -> IO ()
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
poke :: Ptr SurfaceKHR -> SurfaceKHR -> IO ()
$cpoke :: Ptr SurfaceKHR -> SurfaceKHR -> IO ()
peek :: Ptr SurfaceKHR -> IO SurfaceKHR
$cpeek :: Ptr SurfaceKHR -> IO SurfaceKHR
pokeByteOff :: Ptr b -> Int -> SurfaceKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SurfaceKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO SurfaceKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SurfaceKHR
pokeElemOff :: Ptr SurfaceKHR -> Int -> SurfaceKHR -> IO ()
$cpokeElemOff :: Ptr SurfaceKHR -> Int -> SurfaceKHR -> IO ()
peekElemOff :: Ptr SurfaceKHR -> Int -> IO SurfaceKHR
$cpeekElemOff :: Ptr SurfaceKHR -> Int -> IO SurfaceKHR
alignment :: SurfaceKHR -> Int
$calignment :: SurfaceKHR -> Int
sizeOf :: SurfaceKHR -> Int
$csizeOf :: SurfaceKHR -> Int
Storable, SurfaceKHR
SurfaceKHR -> Zero SurfaceKHR
forall a. a -> Zero a
zero :: SurfaceKHR
$czero :: SurfaceKHR
Zero)
  deriving anyclass (Eq SurfaceKHR
Zero SurfaceKHR
(Eq SurfaceKHR, Zero SurfaceKHR) => IsHandle SurfaceKHR
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero SurfaceKHR
$cp1IsHandle :: Eq SurfaceKHR
IsHandle)
instance HasObjectType SurfaceKHR where
  objectTypeAndHandle :: SurfaceKHR -> (ObjectType, Word64)
objectTypeAndHandle (SurfaceKHR h :: Word64
h) = (ObjectType
OBJECT_TYPE_SURFACE_KHR, Word64
h)
instance Show SurfaceKHR where
  showsPrec :: Int -> SurfaceKHR -> ShowS
showsPrec p :: Int
p (SurfaceKHR x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "SurfaceKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show 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 presented 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 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
--
-- '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_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_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_EXT_full_screen_exclusive.releaseFullScreenExclusiveModeEXT',
-- 'Vulkan.Extensions.VK_EXT_hdr_metadata.setHdrMetadataEXT',
-- 'Vulkan.Extensions.VK_AMD_display_native_hdr.setLocalDimmingAMD'
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
/= :: SwapchainKHR -> SwapchainKHR -> Bool
$c/= :: SwapchainKHR -> SwapchainKHR -> Bool
== :: SwapchainKHR -> SwapchainKHR -> Bool
$c== :: 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
min :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
$cmin :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
max :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
$cmax :: SwapchainKHR -> SwapchainKHR -> SwapchainKHR
>= :: SwapchainKHR -> SwapchainKHR -> Bool
$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
compare :: SwapchainKHR -> SwapchainKHR -> Ordering
$ccompare :: SwapchainKHR -> SwapchainKHR -> Ordering
$cp1Ord :: Eq SwapchainKHR
Ord, Ptr b -> Int -> IO SwapchainKHR
Ptr b -> Int -> SwapchainKHR -> IO ()
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
poke :: Ptr SwapchainKHR -> SwapchainKHR -> IO ()
$cpoke :: Ptr SwapchainKHR -> SwapchainKHR -> IO ()
peek :: Ptr SwapchainKHR -> IO SwapchainKHR
$cpeek :: Ptr SwapchainKHR -> IO SwapchainKHR
pokeByteOff :: Ptr b -> Int -> SwapchainKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SwapchainKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO SwapchainKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SwapchainKHR
pokeElemOff :: Ptr SwapchainKHR -> Int -> SwapchainKHR -> IO ()
$cpokeElemOff :: Ptr SwapchainKHR -> Int -> SwapchainKHR -> IO ()
peekElemOff :: Ptr SwapchainKHR -> Int -> IO SwapchainKHR
$cpeekElemOff :: Ptr SwapchainKHR -> Int -> IO SwapchainKHR
alignment :: SwapchainKHR -> Int
$calignment :: SwapchainKHR -> Int
sizeOf :: SwapchainKHR -> Int
$csizeOf :: SwapchainKHR -> Int
Storable, SwapchainKHR
SwapchainKHR -> Zero SwapchainKHR
forall a. a -> Zero a
zero :: SwapchainKHR
$czero :: SwapchainKHR
Zero)
  deriving anyclass (Eq SwapchainKHR
Zero SwapchainKHR
(Eq SwapchainKHR, Zero SwapchainKHR) => IsHandle SwapchainKHR
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero SwapchainKHR
$cp1IsHandle :: Eq SwapchainKHR
IsHandle)
instance HasObjectType SwapchainKHR where
  objectTypeAndHandle :: SwapchainKHR -> (ObjectType, Word64)
objectTypeAndHandle (SwapchainKHR h :: Word64
h) = (ObjectType
OBJECT_TYPE_SWAPCHAIN_KHR, Word64
h)
instance Show SwapchainKHR where
  showsPrec :: Int -> SwapchainKHR -> ShowS
showsPrec p :: Int
p (SwapchainKHR x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "SwapchainKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)


-- | VkDebugReportCallbackEXT - Opaque handle to a debug report callback
-- object
--
-- = See Also
--
-- '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
/= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c/= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
== :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$c== :: 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
min :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
$cmin :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
max :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
$cmax :: DebugReportCallbackEXT
-> DebugReportCallbackEXT -> DebugReportCallbackEXT
>= :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Bool
$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
compare :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Ordering
$ccompare :: DebugReportCallbackEXT -> DebugReportCallbackEXT -> Ordering
$cp1Ord :: Eq DebugReportCallbackEXT
Ord, Ptr b -> Int -> IO DebugReportCallbackEXT
Ptr b -> Int -> DebugReportCallbackEXT -> IO ()
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
poke :: Ptr DebugReportCallbackEXT -> DebugReportCallbackEXT -> IO ()
$cpoke :: Ptr DebugReportCallbackEXT -> DebugReportCallbackEXT -> IO ()
peek :: Ptr DebugReportCallbackEXT -> IO DebugReportCallbackEXT
$cpeek :: Ptr DebugReportCallbackEXT -> IO DebugReportCallbackEXT
pokeByteOff :: Ptr b -> Int -> DebugReportCallbackEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DebugReportCallbackEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO DebugReportCallbackEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DebugReportCallbackEXT
pokeElemOff :: Ptr DebugReportCallbackEXT
-> Int -> DebugReportCallbackEXT -> IO ()
$cpokeElemOff :: Ptr DebugReportCallbackEXT
-> Int -> DebugReportCallbackEXT -> IO ()
peekElemOff :: Ptr DebugReportCallbackEXT -> Int -> IO DebugReportCallbackEXT
$cpeekElemOff :: Ptr DebugReportCallbackEXT -> Int -> IO DebugReportCallbackEXT
alignment :: DebugReportCallbackEXT -> Int
$calignment :: DebugReportCallbackEXT -> Int
sizeOf :: DebugReportCallbackEXT -> Int
$csizeOf :: DebugReportCallbackEXT -> Int
Storable, DebugReportCallbackEXT
DebugReportCallbackEXT -> Zero DebugReportCallbackEXT
forall a. a -> Zero a
zero :: DebugReportCallbackEXT
$czero :: DebugReportCallbackEXT
Zero)
  deriving anyclass (Eq DebugReportCallbackEXT
Zero DebugReportCallbackEXT
(Eq DebugReportCallbackEXT, Zero DebugReportCallbackEXT) =>
IsHandle DebugReportCallbackEXT
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DebugReportCallbackEXT
$cp1IsHandle :: Eq DebugReportCallbackEXT
IsHandle)
instance HasObjectType DebugReportCallbackEXT where
  objectTypeAndHandle :: DebugReportCallbackEXT -> (ObjectType, Word64)
objectTypeAndHandle (DebugReportCallbackEXT h :: Word64
h) = (ObjectType
OBJECT_TYPE_DEBUG_REPORT_CALLBACK_EXT, Word64
h)
instance Show DebugReportCallbackEXT where
  showsPrec :: Int -> DebugReportCallbackEXT -> ShowS
showsPrec p :: Int
p (DebugReportCallbackEXT x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DebugReportCallbackEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show 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
--
-- '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
/= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c/= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
== :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$c== :: 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
min :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
$cmin :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
max :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
$cmax :: DebugUtilsMessengerEXT
-> DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT
>= :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool
$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
compare :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Ordering
$ccompare :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Ordering
$cp1Ord :: Eq DebugUtilsMessengerEXT
Ord, Ptr b -> Int -> IO DebugUtilsMessengerEXT
Ptr b -> Int -> DebugUtilsMessengerEXT -> IO ()
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
poke :: Ptr DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> IO ()
$cpoke :: Ptr DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> IO ()
peek :: Ptr DebugUtilsMessengerEXT -> IO DebugUtilsMessengerEXT
$cpeek :: Ptr DebugUtilsMessengerEXT -> IO DebugUtilsMessengerEXT
pokeByteOff :: Ptr b -> Int -> DebugUtilsMessengerEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DebugUtilsMessengerEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO DebugUtilsMessengerEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DebugUtilsMessengerEXT
pokeElemOff :: Ptr DebugUtilsMessengerEXT
-> Int -> DebugUtilsMessengerEXT -> IO ()
$cpokeElemOff :: Ptr DebugUtilsMessengerEXT
-> Int -> DebugUtilsMessengerEXT -> IO ()
peekElemOff :: Ptr DebugUtilsMessengerEXT -> Int -> IO DebugUtilsMessengerEXT
$cpeekElemOff :: Ptr DebugUtilsMessengerEXT -> Int -> IO DebugUtilsMessengerEXT
alignment :: DebugUtilsMessengerEXT -> Int
$calignment :: DebugUtilsMessengerEXT -> Int
sizeOf :: DebugUtilsMessengerEXT -> Int
$csizeOf :: DebugUtilsMessengerEXT -> Int
Storable, DebugUtilsMessengerEXT
DebugUtilsMessengerEXT -> Zero DebugUtilsMessengerEXT
forall a. a -> Zero a
zero :: DebugUtilsMessengerEXT
$czero :: DebugUtilsMessengerEXT
Zero)
  deriving anyclass (Eq DebugUtilsMessengerEXT
Zero DebugUtilsMessengerEXT
(Eq DebugUtilsMessengerEXT, Zero DebugUtilsMessengerEXT) =>
IsHandle DebugUtilsMessengerEXT
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DebugUtilsMessengerEXT
$cp1IsHandle :: Eq DebugUtilsMessengerEXT
IsHandle)
instance HasObjectType DebugUtilsMessengerEXT where
  objectTypeAndHandle :: DebugUtilsMessengerEXT -> (ObjectType, Word64)
objectTypeAndHandle (DebugUtilsMessengerEXT h :: Word64
h) = (ObjectType
OBJECT_TYPE_DEBUG_UTILS_MESSENGER_EXT, Word64
h)
instance Show DebugUtilsMessengerEXT where
  showsPrec :: Int -> DebugUtilsMessengerEXT -> ShowS
showsPrec p :: Int
p (DebugUtilsMessengerEXT x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DebugUtilsMessengerEXT 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word64
x)