{-# language CPP #-}
module Vulkan.Core10.Handles  ( Instance(..)
                              , Instance_T
                              , PhysicalDevice(..)
                              , PhysicalDevice_T
                              , Device(..)
                              , Device_T
                              , Queue(..)
                              , Queue_T
                              , CommandBuffer(..)
                              , CommandBuffer_T
                              , DeviceMemory(..)
                              , CommandPool(..)
                              , Buffer(..)
                              , BufferView(..)
                              , Image(..)
                              , ImageView(..)
                              , ShaderModule(..)
                              , Pipeline(..)
                              , PipelineLayout(..)
                              , Sampler(..)
                              , DescriptorSet(..)
                              , DescriptorSetLayout(..)
                              , DescriptorPool(..)
                              , Fence(..)
                              , Semaphore(..)
                              , Event(..)
                              , QueryPool(..)
                              , Framebuffer(..)
                              , RenderPass(..)
                              , PipelineCache(..)
                              ) where

import Foreign.Ptr (ptrToWordPtr)
import GHC.Show (showParen)
import Numeric (showHex)
import Foreign.Ptr (pattern WordPtr)
import Foreign.Storable (Storable)
import Foreign.Ptr (Ptr)
import Data.Word (Word64)
import Vulkan.Dynamic (DeviceCmds)
import Vulkan.Core10.APIConstants (HasObjectType(..))
import Vulkan.Dynamic (InstanceCmds)
import Vulkan.Core10.APIConstants (IsHandle)
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_BUFFER))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_BUFFER_VIEW))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_COMMAND_BUFFER))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_COMMAND_POOL))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DESCRIPTOR_POOL))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DESCRIPTOR_SET))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DEVICE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_DEVICE_MEMORY))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_EVENT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_FENCE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_FRAMEBUFFER))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_IMAGE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_IMAGE_VIEW))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_INSTANCE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_PHYSICAL_DEVICE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_PIPELINE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_PIPELINE_CACHE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_PIPELINE_LAYOUT))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_QUERY_POOL))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_QUEUE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_RENDER_PASS))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SAMPLER))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SEMAPHORE))
import Vulkan.Core10.Enums.ObjectType (ObjectType(OBJECT_TYPE_SHADER_MODULE))
-- | An opaque type for representing pointers to VkInstance handles
data Instance_T
-- | VkInstance - Opaque handle to an instance object
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_android_surface.createAndroidSurfaceKHR',
-- 'Vulkan.Extensions.VK_EXT_debug_report.createDebugReportCallbackEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.createDebugUtilsMessengerEXT',
-- '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.Core10.DeviceInitialization.createInstance',
-- '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_EXT_debug_report.debugReportMessageEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_report.destroyDebugReportCallbackEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.destroyDebugUtilsMessengerEXT',
-- 'Vulkan.Core10.DeviceInitialization.destroyInstance',
-- 'Vulkan.Extensions.VK_KHR_surface.destroySurfaceKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group_creation.enumeratePhysicalDeviceGroups',
-- 'Vulkan.Extensions.VK_KHR_device_group_creation.enumeratePhysicalDeviceGroupsKHR',
-- 'Vulkan.Core10.DeviceInitialization.enumeratePhysicalDevices',
-- 'Vulkan.Core10.DeviceInitialization.getInstanceProcAddr',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.submitDebugUtilsMessageEXT'
data Instance = Instance
  { Instance -> Ptr Instance_T
instanceHandle :: Ptr Instance_T
  , Instance -> InstanceCmds
instanceCmds :: InstanceCmds
  }
  deriving stock (Instance -> Instance -> Bool
(Instance -> Instance -> Bool)
-> (Instance -> Instance -> Bool) -> Eq Instance
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Instance -> Instance -> Bool
$c/= :: Instance -> Instance -> Bool
== :: Instance -> Instance -> Bool
$c== :: Instance -> Instance -> Bool
Eq, Int -> Instance -> ShowS
[Instance] -> ShowS
Instance -> String
(Int -> Instance -> ShowS)
-> (Instance -> String) -> ([Instance] -> ShowS) -> Show Instance
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Instance] -> ShowS
$cshowList :: [Instance] -> ShowS
show :: Instance -> String
$cshow :: Instance -> String
showsPrec :: Int -> Instance -> ShowS
$cshowsPrec :: Int -> Instance -> ShowS
Show)
  deriving anyclass (Eq Instance
Zero Instance
(Eq Instance, Zero Instance) => IsHandle Instance
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Instance
$cp1IsHandle :: Eq Instance
IsHandle)
instance Zero Instance where
  zero :: Instance
zero = Ptr Instance_T -> InstanceCmds -> Instance
Instance Ptr Instance_T
forall a. Zero a => a
zero InstanceCmds
forall a. Zero a => a
zero
instance HasObjectType Instance where
  objectTypeAndHandle :: Instance -> (ObjectType, Word64)
objectTypeAndHandle (Instance (Ptr Instance_T -> WordPtr
forall a. Ptr a -> WordPtr
ptrToWordPtr -> WordPtr h :: Word
h) _) = (ObjectType
OBJECT_TYPE_INSTANCE, Word -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
h)


-- | An opaque type for representing pointers to VkPhysicalDevice handles
data PhysicalDevice_T
-- | VkPhysicalDevice - Opaque handle to a physical device object
--
-- = See Also
--
-- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group_creation.DeviceGroupDeviceCreateInfo',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group_creation.PhysicalDeviceGroupProperties',
-- 'Vulkan.Extensions.VK_EXT_acquire_xlib_display.acquireXlibDisplayEXT',
-- 'Vulkan.Core10.Device.createDevice',
-- 'Vulkan.Extensions.VK_KHR_display.createDisplayModeKHR',
-- 'Vulkan.Core10.ExtensionDiscovery.enumerateDeviceExtensionProperties',
-- 'Vulkan.Core10.LayerDiscovery.enumerateDeviceLayerProperties',
-- 'Vulkan.Extensions.VK_KHR_performance_query.enumeratePhysicalDeviceQueueFamilyPerformanceQueryCountersKHR',
-- 'Vulkan.Core10.DeviceInitialization.enumeratePhysicalDevices',
-- 'Vulkan.Extensions.VK_KHR_get_display_properties2.getDisplayModeProperties2KHR',
-- 'Vulkan.Extensions.VK_KHR_display.getDisplayModePropertiesKHR',
-- 'Vulkan.Extensions.VK_KHR_get_display_properties2.getDisplayPlaneCapabilities2KHR',
-- 'Vulkan.Extensions.VK_KHR_display.getDisplayPlaneCapabilitiesKHR',
-- 'Vulkan.Extensions.VK_KHR_display.getDisplayPlaneSupportedDisplaysKHR',
-- 'Vulkan.Extensions.VK_EXT_calibrated_timestamps.getPhysicalDeviceCalibrateableTimeDomainsEXT',
-- 'Vulkan.Extensions.VK_NV_cooperative_matrix.getPhysicalDeviceCooperativeMatrixPropertiesNV',
-- 'Vulkan.Extensions.VK_EXT_directfb_surface.getPhysicalDeviceDirectFBPresentationSupportEXT',
-- 'Vulkan.Extensions.VK_KHR_get_display_properties2.getPhysicalDeviceDisplayPlaneProperties2KHR',
-- 'Vulkan.Extensions.VK_KHR_display.getPhysicalDeviceDisplayPlanePropertiesKHR',
-- 'Vulkan.Extensions.VK_KHR_get_display_properties2.getPhysicalDeviceDisplayProperties2KHR',
-- 'Vulkan.Extensions.VK_KHR_display.getPhysicalDeviceDisplayPropertiesKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.getPhysicalDeviceExternalBufferProperties',
-- 'Vulkan.Extensions.VK_KHR_external_memory_capabilities.getPhysicalDeviceExternalBufferPropertiesKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_external_fence_capabilities.getPhysicalDeviceExternalFenceProperties',
-- 'Vulkan.Extensions.VK_KHR_external_fence_capabilities.getPhysicalDeviceExternalFencePropertiesKHR',
-- 'Vulkan.Extensions.VK_NV_external_memory_capabilities.getPhysicalDeviceExternalImageFormatPropertiesNV',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_external_semaphore_capabilities.getPhysicalDeviceExternalSemaphoreProperties',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_capabilities.getPhysicalDeviceExternalSemaphorePropertiesKHR',
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceFeatures',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2KHR',
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceFormatProperties',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFormatProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceFormatProperties2KHR',
-- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.getPhysicalDeviceFragmentShadingRatesKHR',
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceImageFormatProperties',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2KHR',
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceMemoryProperties',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceMemoryProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceMemoryProperties2KHR',
-- 'Vulkan.Extensions.VK_EXT_sample_locations.getPhysicalDeviceMultisamplePropertiesEXT',
-- 'Vulkan.Extensions.VK_KHR_swapchain.getPhysicalDevicePresentRectanglesKHR',
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceProperties',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2KHR',
-- 'Vulkan.Extensions.VK_KHR_performance_query.getPhysicalDeviceQueueFamilyPerformanceQueryPassesKHR',
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceQueueFamilyProperties',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceQueueFamilyProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceQueueFamilyProperties2KHR',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.getPhysicalDeviceSparseImageFormatProperties',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceSparseImageFormatProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceSparseImageFormatProperties2KHR',
-- 'Vulkan.Extensions.VK_NV_coverage_reduction_mode.getPhysicalDeviceSupportedFramebufferMixedSamplesCombinationsNV',
-- 'Vulkan.Extensions.VK_EXT_display_surface_counter.getPhysicalDeviceSurfaceCapabilities2EXT',
-- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.getPhysicalDeviceSurfaceCapabilities2KHR',
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceCapabilitiesKHR',
-- 'Vulkan.Extensions.VK_KHR_get_surface_capabilities2.getPhysicalDeviceSurfaceFormats2KHR',
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceFormatsKHR',
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.getPhysicalDeviceSurfacePresentModes2EXT',
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfacePresentModesKHR',
-- 'Vulkan.Extensions.VK_KHR_surface.getPhysicalDeviceSurfaceSupportKHR',
-- 'Vulkan.Extensions.VK_EXT_tooling_info.getPhysicalDeviceToolPropertiesEXT',
-- 'Vulkan.Extensions.VK_KHR_wayland_surface.getPhysicalDeviceWaylandPresentationSupportKHR',
-- 'Vulkan.Extensions.VK_KHR_win32_surface.getPhysicalDeviceWin32PresentationSupportKHR',
-- 'Vulkan.Extensions.VK_KHR_xcb_surface.getPhysicalDeviceXcbPresentationSupportKHR',
-- 'Vulkan.Extensions.VK_KHR_xlib_surface.getPhysicalDeviceXlibPresentationSupportKHR',
-- 'Vulkan.Extensions.VK_EXT_acquire_xlib_display.getRandROutputDisplayEXT',
-- 'Vulkan.Extensions.VK_EXT_direct_mode_display.releaseDisplayEXT'
data PhysicalDevice = PhysicalDevice
  { PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle :: Ptr PhysicalDevice_T
  , PhysicalDevice -> InstanceCmds
instanceCmds :: InstanceCmds
  }
  deriving stock (PhysicalDevice -> PhysicalDevice -> Bool
(PhysicalDevice -> PhysicalDevice -> Bool)
-> (PhysicalDevice -> PhysicalDevice -> Bool) -> Eq PhysicalDevice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevice -> PhysicalDevice -> Bool
$c/= :: PhysicalDevice -> PhysicalDevice -> Bool
== :: PhysicalDevice -> PhysicalDevice -> Bool
$c== :: PhysicalDevice -> PhysicalDevice -> Bool
Eq, Int -> PhysicalDevice -> ShowS
[PhysicalDevice] -> ShowS
PhysicalDevice -> String
(Int -> PhysicalDevice -> ShowS)
-> (PhysicalDevice -> String)
-> ([PhysicalDevice] -> ShowS)
-> Show PhysicalDevice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PhysicalDevice] -> ShowS
$cshowList :: [PhysicalDevice] -> ShowS
show :: PhysicalDevice -> String
$cshow :: PhysicalDevice -> String
showsPrec :: Int -> PhysicalDevice -> ShowS
$cshowsPrec :: Int -> PhysicalDevice -> ShowS
Show)
  deriving anyclass (Eq PhysicalDevice
Zero PhysicalDevice
(Eq PhysicalDevice, Zero PhysicalDevice) => IsHandle PhysicalDevice
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero PhysicalDevice
$cp1IsHandle :: Eq PhysicalDevice
IsHandle)
instance Zero PhysicalDevice where
  zero :: PhysicalDevice
zero = Ptr PhysicalDevice_T -> InstanceCmds -> PhysicalDevice
PhysicalDevice Ptr PhysicalDevice_T
forall a. Zero a => a
zero InstanceCmds
forall a. Zero a => a
zero
instance HasObjectType PhysicalDevice where
  objectTypeAndHandle :: PhysicalDevice -> (ObjectType, Word64)
objectTypeAndHandle (PhysicalDevice (Ptr PhysicalDevice_T -> WordPtr
forall a. Ptr a -> WordPtr
ptrToWordPtr -> WordPtr h :: Word
h) _) = (ObjectType
OBJECT_TYPE_PHYSICAL_DEVICE, Word -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
h)


-- | An opaque type for representing pointers to VkDevice handles
data Device_T
-- | VkDevice - Opaque handle to a device object
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.acquireFullScreenExclusiveModeEXT',
-- 'Vulkan.Extensions.VK_KHR_swapchain.acquireNextImage2KHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.acquireNextImageKHR',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.acquirePerformanceConfigurationINTEL',
-- 'Vulkan.Extensions.VK_KHR_performance_query.acquireProfilingLockKHR',
-- 'Vulkan.Core10.CommandBuffer.allocateCommandBuffers',
-- 'Vulkan.Core10.DescriptorSet.allocateDescriptorSets',
-- 'Vulkan.Core10.Memory.allocateMemory',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.bindAccelerationStructureMemoryKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.bindAccelerationStructureMemoryNV',
-- 'Vulkan.Core10.MemoryManagement.bindBufferMemory',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_bind_memory2.bindBufferMemory2',
-- 'Vulkan.Extensions.VK_KHR_bind_memory2.bindBufferMemory2KHR',
-- 'Vulkan.Core10.MemoryManagement.bindImageMemory',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_bind_memory2.bindImageMemory2',
-- 'Vulkan.Extensions.VK_KHR_bind_memory2.bindImageMemory2KHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.buildAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.compileDeferredNV',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.copyAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.copyAccelerationStructureToMemoryKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.copyMemoryToAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.createAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.createAccelerationStructureNV',
-- 'Vulkan.Core10.Buffer.createBuffer',
-- 'Vulkan.Core10.BufferView.createBufferView',
-- 'Vulkan.Core10.CommandPool.createCommandPool',
-- 'Vulkan.Core10.Pipeline.createComputePipelines',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.createDeferredOperationKHR',
-- 'Vulkan.Core10.DescriptorSet.createDescriptorPool',
-- 'Vulkan.Core10.DescriptorSet.createDescriptorSetLayout',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_descriptor_update_template.createDescriptorUpdateTemplate',
-- 'Vulkan.Extensions.VK_KHR_descriptor_update_template.createDescriptorUpdateTemplateKHR',
-- 'Vulkan.Core10.Device.createDevice', 'Vulkan.Core10.Event.createEvent',
-- 'Vulkan.Core10.Fence.createFence',
-- 'Vulkan.Core10.Pass.createFramebuffer',
-- 'Vulkan.Core10.Pipeline.createGraphicsPipelines',
-- 'Vulkan.Core10.Image.createImage',
-- 'Vulkan.Core10.ImageView.createImageView',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.createIndirectCommandsLayoutNV',
-- 'Vulkan.Core10.PipelineCache.createPipelineCache',
-- 'Vulkan.Core10.PipelineLayout.createPipelineLayout',
-- 'Vulkan.Extensions.VK_EXT_private_data.createPrivateDataSlotEXT',
-- 'Vulkan.Core10.Query.createQueryPool',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.createRayTracingPipelinesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.createRayTracingPipelinesNV',
-- 'Vulkan.Core10.Pass.createRenderPass',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.createRenderPass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.createRenderPass2KHR',
-- 'Vulkan.Core10.Sampler.createSampler',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.createSamplerYcbcrConversion',
-- 'Vulkan.Extensions.VK_KHR_sampler_ycbcr_conversion.createSamplerYcbcrConversionKHR',
-- 'Vulkan.Core10.QueueSemaphore.createSemaphore',
-- 'Vulkan.Core10.Shader.createShaderModule',
-- 'Vulkan.Extensions.VK_KHR_display_swapchain.createSharedSwapchainsKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.createSwapchainKHR',
-- 'Vulkan.Extensions.VK_EXT_validation_cache.createValidationCacheEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_marker.debugMarkerSetObjectNameEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_marker.debugMarkerSetObjectTagEXT',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.deferredOperationJoinKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.destroyAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.destroyAccelerationStructureNV',
-- 'Vulkan.Core10.Buffer.destroyBuffer',
-- 'Vulkan.Core10.BufferView.destroyBufferView',
-- 'Vulkan.Core10.CommandPool.destroyCommandPool',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.destroyDeferredOperationKHR',
-- 'Vulkan.Core10.DescriptorSet.destroyDescriptorPool',
-- 'Vulkan.Core10.DescriptorSet.destroyDescriptorSetLayout',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_descriptor_update_template.destroyDescriptorUpdateTemplate',
-- 'Vulkan.Extensions.VK_KHR_descriptor_update_template.destroyDescriptorUpdateTemplateKHR',
-- 'Vulkan.Core10.Device.destroyDevice',
-- 'Vulkan.Core10.Event.destroyEvent', 'Vulkan.Core10.Fence.destroyFence',
-- 'Vulkan.Core10.Pass.destroyFramebuffer',
-- 'Vulkan.Core10.Image.destroyImage',
-- 'Vulkan.Core10.ImageView.destroyImageView',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.destroyIndirectCommandsLayoutNV',
-- 'Vulkan.Core10.Pipeline.destroyPipeline',
-- 'Vulkan.Core10.PipelineCache.destroyPipelineCache',
-- 'Vulkan.Core10.PipelineLayout.destroyPipelineLayout',
-- 'Vulkan.Extensions.VK_EXT_private_data.destroyPrivateDataSlotEXT',
-- 'Vulkan.Core10.Query.destroyQueryPool',
-- 'Vulkan.Core10.Pass.destroyRenderPass',
-- 'Vulkan.Core10.Sampler.destroySampler',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.destroySamplerYcbcrConversion',
-- 'Vulkan.Extensions.VK_KHR_sampler_ycbcr_conversion.destroySamplerYcbcrConversionKHR',
-- 'Vulkan.Core10.QueueSemaphore.destroySemaphore',
-- 'Vulkan.Core10.Shader.destroyShaderModule',
-- 'Vulkan.Extensions.VK_KHR_swapchain.destroySwapchainKHR',
-- 'Vulkan.Extensions.VK_EXT_validation_cache.destroyValidationCacheEXT',
-- 'Vulkan.Core10.Queue.deviceWaitIdle',
-- 'Vulkan.Extensions.VK_EXT_display_control.displayPowerControlEXT',
-- 'Vulkan.Core10.Memory.flushMappedMemoryRanges',
-- 'Vulkan.Core10.CommandBuffer.freeCommandBuffers',
-- 'Vulkan.Core10.DescriptorSet.freeDescriptorSets',
-- 'Vulkan.Core10.Memory.freeMemory',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.getAccelerationStructureDeviceAddressKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.getAccelerationStructureHandleNV',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.getAccelerationStructureMemoryRequirementsKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.getAccelerationStructureMemoryRequirementsNV',
-- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.getAndroidHardwareBufferPropertiesANDROID',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.getBufferDeviceAddress',
-- 'Vulkan.Extensions.VK_EXT_buffer_device_address.getBufferDeviceAddressEXT',
-- 'Vulkan.Extensions.VK_KHR_buffer_device_address.getBufferDeviceAddressKHR',
-- 'Vulkan.Core10.MemoryManagement.getBufferMemoryRequirements',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getBufferMemoryRequirements2',
-- 'Vulkan.Extensions.VK_KHR_get_memory_requirements2.getBufferMemoryRequirements2KHR',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.getBufferOpaqueCaptureAddress',
-- 'Vulkan.Extensions.VK_KHR_buffer_device_address.getBufferOpaqueCaptureAddressKHR',
-- 'Vulkan.Extensions.VK_EXT_calibrated_timestamps.getCalibratedTimestampsEXT',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.getDeferredOperationMaxConcurrencyKHR',
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.getDeferredOperationResultKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance3.getDescriptorSetLayoutSupport',
-- 'Vulkan.Extensions.VK_KHR_maintenance3.getDescriptorSetLayoutSupportKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.getDeviceAccelerationStructureCompatibilityKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.getDeviceGroupPeerMemoryFeatures',
-- 'Vulkan.Extensions.VK_KHR_device_group.getDeviceGroupPeerMemoryFeaturesKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.getDeviceGroupPresentCapabilitiesKHR',
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.getDeviceGroupSurfacePresentModes2EXT',
-- 'Vulkan.Extensions.VK_KHR_swapchain.getDeviceGroupSurfacePresentModesKHR',
-- 'Vulkan.Core10.Memory.getDeviceMemoryCommitment',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.getDeviceMemoryOpaqueCaptureAddress',
-- 'Vulkan.Extensions.VK_KHR_buffer_device_address.getDeviceMemoryOpaqueCaptureAddressKHR',
-- 'Vulkan.Core10.DeviceInitialization.getDeviceProcAddr',
-- 'Vulkan.Core10.Queue.getDeviceQueue',
-- 'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.getDeviceQueue2',
-- 'Vulkan.Core10.Event.getEventStatus',
-- 'Vulkan.Extensions.VK_KHR_external_fence_fd.getFenceFdKHR',
-- 'Vulkan.Core10.Fence.getFenceStatus',
-- 'Vulkan.Extensions.VK_KHR_external_fence_win32.getFenceWin32HandleKHR',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.getGeneratedCommandsMemoryRequirementsNV',
-- 'Vulkan.Extensions.VK_EXT_image_drm_format_modifier.getImageDrmFormatModifierPropertiesEXT',
-- 'Vulkan.Core10.MemoryManagement.getImageMemoryRequirements',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getImageMemoryRequirements2',
-- 'Vulkan.Extensions.VK_KHR_get_memory_requirements2.getImageMemoryRequirements2KHR',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.getImageSparseMemoryRequirements',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.getImageSparseMemoryRequirements2',
-- 'Vulkan.Extensions.VK_KHR_get_memory_requirements2.getImageSparseMemoryRequirements2KHR',
-- 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- 'Vulkan.Extensions.VK_NVX_image_view_handle.getImageViewAddressNVX',
-- 'Vulkan.Extensions.VK_NVX_image_view_handle.getImageViewHandleNVX',
-- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.getMemoryAndroidHardwareBufferANDROID',
-- 'Vulkan.Extensions.VK_KHR_external_memory_fd.getMemoryFdKHR',
-- 'Vulkan.Extensions.VK_KHR_external_memory_fd.getMemoryFdPropertiesKHR',
-- 'Vulkan.Extensions.VK_EXT_external_memory_host.getMemoryHostPointerPropertiesEXT',
-- 'Vulkan.Extensions.VK_KHR_external_memory_win32.getMemoryWin32HandleKHR',
-- 'Vulkan.Extensions.VK_NV_external_memory_win32.getMemoryWin32HandleNV',
-- 'Vulkan.Extensions.VK_KHR_external_memory_win32.getMemoryWin32HandlePropertiesKHR',
-- 'Vulkan.Extensions.VK_GOOGLE_display_timing.getPastPresentationTimingGOOGLE',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.getPerformanceParameterINTEL',
-- 'Vulkan.Core10.PipelineCache.getPipelineCacheData',
-- 'Vulkan.Extensions.VK_KHR_pipeline_executable_properties.getPipelineExecutableInternalRepresentationsKHR',
-- 'Vulkan.Extensions.VK_KHR_pipeline_executable_properties.getPipelineExecutablePropertiesKHR',
-- 'Vulkan.Extensions.VK_KHR_pipeline_executable_properties.getPipelineExecutableStatisticsKHR',
-- 'Vulkan.Extensions.VK_EXT_private_data.getPrivateDataEXT',
-- 'Vulkan.Core10.Query.getQueryPoolResults',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.getRayTracingCaptureReplayShaderGroupHandlesKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.getRayTracingShaderGroupHandlesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.getRayTracingShaderGroupHandlesNV',
-- 'Vulkan.Extensions.VK_GOOGLE_display_timing.getRefreshCycleDurationGOOGLE',
-- 'Vulkan.Core10.Pass.getRenderAreaGranularity',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.getSemaphoreCounterValue',
-- 'Vulkan.Extensions.VK_KHR_timeline_semaphore.getSemaphoreCounterValueKHR',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_fd.getSemaphoreFdKHR',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_win32.getSemaphoreWin32HandleKHR',
-- 'Vulkan.Extensions.VK_AMD_shader_info.getShaderInfoAMD',
-- '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_validation_cache.getValidationCacheDataEXT',
-- 'Vulkan.Extensions.VK_KHR_external_fence_fd.importFenceFdKHR',
-- 'Vulkan.Extensions.VK_KHR_external_fence_win32.importFenceWin32HandleKHR',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_fd.importSemaphoreFdKHR',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_win32.importSemaphoreWin32HandleKHR',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.initializePerformanceApiINTEL',
-- 'Vulkan.Core10.Memory.invalidateMappedMemoryRanges',
-- 'Vulkan.Core10.Memory.mapMemory',
-- 'Vulkan.Core10.PipelineCache.mergePipelineCaches',
-- 'Vulkan.Extensions.VK_EXT_validation_cache.mergeValidationCachesEXT',
-- 'Vulkan.Extensions.VK_EXT_display_control.registerDeviceEventEXT',
-- 'Vulkan.Extensions.VK_EXT_display_control.registerDisplayEventEXT',
-- 'Vulkan.Extensions.VK_EXT_full_screen_exclusive.releaseFullScreenExclusiveModeEXT',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.releasePerformanceConfigurationINTEL',
-- 'Vulkan.Extensions.VK_KHR_performance_query.releaseProfilingLockKHR',
-- 'Vulkan.Core10.CommandPool.resetCommandPool',
-- 'Vulkan.Core10.DescriptorSet.resetDescriptorPool',
-- 'Vulkan.Core10.Event.resetEvent', 'Vulkan.Core10.Fence.resetFences',
-- 'Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset.resetQueryPool',
-- 'Vulkan.Extensions.VK_EXT_host_query_reset.resetQueryPoolEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.setDebugUtilsObjectNameEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.setDebugUtilsObjectTagEXT',
-- 'Vulkan.Core10.Event.setEvent',
-- 'Vulkan.Extensions.VK_EXT_hdr_metadata.setHdrMetadataEXT',
-- 'Vulkan.Extensions.VK_AMD_display_native_hdr.setLocalDimmingAMD',
-- 'Vulkan.Extensions.VK_EXT_private_data.setPrivateDataEXT',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.signalSemaphore',
-- 'Vulkan.Extensions.VK_KHR_timeline_semaphore.signalSemaphoreKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance1.trimCommandPool',
-- 'Vulkan.Extensions.VK_KHR_maintenance1.trimCommandPoolKHR',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.uninitializePerformanceApiINTEL',
-- 'Vulkan.Core10.Memory.unmapMemory',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_descriptor_update_template.updateDescriptorSetWithTemplate',
-- 'Vulkan.Extensions.VK_KHR_descriptor_update_template.updateDescriptorSetWithTemplateKHR',
-- 'Vulkan.Core10.DescriptorSet.updateDescriptorSets',
-- 'Vulkan.Core10.Fence.waitForFences',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.waitSemaphores',
-- 'Vulkan.Extensions.VK_KHR_timeline_semaphore.waitSemaphoresKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.writeAccelerationStructuresPropertiesKHR'
data Device = Device
  { Device -> Ptr Device_T
deviceHandle :: Ptr Device_T
  , Device -> DeviceCmds
deviceCmds :: DeviceCmds
  }
  deriving stock (Device -> Device -> Bool
(Device -> Device -> Bool)
-> (Device -> Device -> Bool) -> Eq Device
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Device -> Device -> Bool
$c/= :: Device -> Device -> Bool
== :: Device -> Device -> Bool
$c== :: Device -> Device -> Bool
Eq, Int -> Device -> ShowS
[Device] -> ShowS
Device -> String
(Int -> Device -> ShowS)
-> (Device -> String) -> ([Device] -> ShowS) -> Show Device
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Device] -> ShowS
$cshowList :: [Device] -> ShowS
show :: Device -> String
$cshow :: Device -> String
showsPrec :: Int -> Device -> ShowS
$cshowsPrec :: Int -> Device -> ShowS
Show)
  deriving anyclass (Eq Device
Zero Device
(Eq Device, Zero Device) => IsHandle Device
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Device
$cp1IsHandle :: Eq Device
IsHandle)
instance Zero Device where
  zero :: Device
zero = Ptr Device_T -> DeviceCmds -> Device
Device Ptr Device_T
forall a. Zero a => a
zero DeviceCmds
forall a. Zero a => a
zero
instance HasObjectType Device where
  objectTypeAndHandle :: Device -> (ObjectType, Word64)
objectTypeAndHandle (Device (Ptr Device_T -> WordPtr
forall a. Ptr a -> WordPtr
ptrToWordPtr -> WordPtr h :: Word
h) _) = (ObjectType
OBJECT_TYPE_DEVICE, Word -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
h)


-- | An opaque type for representing pointers to VkQueue handles
data Queue_T
-- | VkQueue - Opaque handle to a queue object
--
-- = See Also
--
-- 'Vulkan.Core10.Queue.getDeviceQueue',
-- 'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.getDeviceQueue2',
-- 'Vulkan.Extensions.VK_NV_device_diagnostic_checkpoints.getQueueCheckpointDataNV',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.queueBeginDebugUtilsLabelEXT',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.queueBindSparse',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.queueEndDebugUtilsLabelEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.queueInsertDebugUtilsLabelEXT',
-- 'Vulkan.Extensions.VK_KHR_swapchain.queuePresentKHR',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.queueSetPerformanceConfigurationINTEL',
-- 'Vulkan.Core10.Queue.queueSubmit', 'Vulkan.Core10.Queue.queueWaitIdle'
data Queue = Queue
  { Queue -> Ptr Queue_T
queueHandle :: Ptr Queue_T
  , Queue -> DeviceCmds
deviceCmds :: DeviceCmds
  }
  deriving stock (Queue -> Queue -> Bool
(Queue -> Queue -> Bool) -> (Queue -> Queue -> Bool) -> Eq Queue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Queue -> Queue -> Bool
$c/= :: Queue -> Queue -> Bool
== :: Queue -> Queue -> Bool
$c== :: Queue -> Queue -> Bool
Eq, Int -> Queue -> ShowS
[Queue] -> ShowS
Queue -> String
(Int -> Queue -> ShowS)
-> (Queue -> String) -> ([Queue] -> ShowS) -> Show Queue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Queue] -> ShowS
$cshowList :: [Queue] -> ShowS
show :: Queue -> String
$cshow :: Queue -> String
showsPrec :: Int -> Queue -> ShowS
$cshowsPrec :: Int -> Queue -> ShowS
Show)
  deriving anyclass (Eq Queue
Zero Queue
(Eq Queue, Zero Queue) => IsHandle Queue
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Queue
$cp1IsHandle :: Eq Queue
IsHandle)
instance Zero Queue where
  zero :: Queue
zero = Ptr Queue_T -> DeviceCmds -> Queue
Queue Ptr Queue_T
forall a. Zero a => a
zero DeviceCmds
forall a. Zero a => a
zero
instance HasObjectType Queue where
  objectTypeAndHandle :: Queue -> (ObjectType, Word64)
objectTypeAndHandle (Queue (Ptr Queue_T -> WordPtr
forall a. Ptr a -> WordPtr
ptrToWordPtr -> WordPtr h :: Word
h) _) = (ObjectType
OBJECT_TYPE_QUEUE, Word -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
h)


-- | An opaque type for representing pointers to VkCommandBuffer handles
data CommandBuffer_T
-- | VkCommandBuffer - Opaque handle to a command buffer object
--
-- = See Also
--
-- 'Vulkan.Core10.Queue.SubmitInfo',
-- 'Vulkan.Core10.CommandBuffer.allocateCommandBuffers',
-- 'Vulkan.Core10.CommandBuffer.beginCommandBuffer',
-- 'Vulkan.Extensions.VK_EXT_conditional_rendering.cmdBeginConditionalRenderingEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.cmdBeginDebugUtilsLabelEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBeginQuery',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdBeginQueryIndexedEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBeginRenderPass',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.cmdBeginRenderPass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.cmdBeginRenderPass2KHR',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdBeginTransformFeedbackEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBindDescriptorSets',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBindIndexBuffer',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBindPipeline',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.cmdBindPipelineShaderGroupNV',
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdBindShadingRateImageNV',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdBindTransformFeedbackBuffersEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBindVertexBuffers',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBlitImage',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.cmdBlitImage2KHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdBuildAccelerationStructureIndirectKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdBuildAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdBuildAccelerationStructureNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearAttachments',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearColorImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearDepthStencilImage',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdCopyAccelerationStructureKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdCopyAccelerationStructureNV',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdCopyAccelerationStructureToMemoryKHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyBuffer',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.cmdCopyBuffer2KHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyBufferToImage',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.cmdCopyBufferToImage2KHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyImage',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.cmdCopyImage2KHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyImageToBuffer',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.cmdCopyImageToBuffer2KHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdCopyMemoryToAccelerationStructureKHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyQueryPoolResults',
-- 'Vulkan.Extensions.VK_EXT_debug_marker.cmdDebugMarkerBeginEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_marker.cmdDebugMarkerEndEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_marker.cmdDebugMarkerInsertEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDispatch',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.cmdDispatchBase',
-- 'Vulkan.Extensions.VK_KHR_device_group.cmdDispatchBaseKHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDispatchIndirect',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDraw',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndexed',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndexedIndirect',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_draw_indirect_count.cmdDrawIndexedIndirectCount',
-- 'Vulkan.Extensions.VK_AMD_draw_indirect_count.cmdDrawIndexedIndirectCountAMD',
-- 'Vulkan.Extensions.VK_KHR_draw_indirect_count.cmdDrawIndexedIndirectCountKHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndirect',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdDrawIndirectByteCountEXT',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_draw_indirect_count.cmdDrawIndirectCount',
-- 'Vulkan.Extensions.VK_AMD_draw_indirect_count.cmdDrawIndirectCountAMD',
-- 'Vulkan.Extensions.VK_KHR_draw_indirect_count.cmdDrawIndirectCountKHR',
-- 'Vulkan.Extensions.VK_NV_mesh_shader.cmdDrawMeshTasksIndirectCountNV',
-- 'Vulkan.Extensions.VK_NV_mesh_shader.cmdDrawMeshTasksIndirectNV',
-- 'Vulkan.Extensions.VK_NV_mesh_shader.cmdDrawMeshTasksNV',
-- 'Vulkan.Extensions.VK_EXT_conditional_rendering.cmdEndConditionalRenderingEXT',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.cmdEndDebugUtilsLabelEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdEndQuery',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndQueryIndexedEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdEndRenderPass',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.cmdEndRenderPass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.cmdEndRenderPass2KHR',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndTransformFeedbackEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdExecuteCommands',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.cmdExecuteGeneratedCommandsNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdFillBuffer',
-- 'Vulkan.Extensions.VK_EXT_debug_utils.cmdInsertDebugUtilsLabelEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdNextSubpass',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.cmdNextSubpass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.cmdNextSubpass2KHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdPipelineBarrier',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.cmdPreprocessGeneratedCommandsNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdPushConstants',
-- 'Vulkan.Extensions.VK_KHR_push_descriptor.cmdPushDescriptorSetKHR',
-- 'Vulkan.Extensions.VK_KHR_push_descriptor.cmdPushDescriptorSetWithTemplateKHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdResetEvent',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdResetQueryPool',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdResolveImage',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.cmdResolveImage2KHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetBlendConstants',
-- 'Vulkan.Extensions.VK_NV_device_diagnostic_checkpoints.cmdSetCheckpointNV',
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetCoarseSampleOrderNV',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetCullModeEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetDepthBias',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetDepthBounds',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetDepthBoundsTestEnableEXT',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetDepthCompareOpEXT',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetDepthTestEnableEXT',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetDepthWriteEnableEXT',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.cmdSetDeviceMask',
-- 'Vulkan.Extensions.VK_KHR_device_group.cmdSetDeviceMaskKHR',
-- 'Vulkan.Extensions.VK_EXT_discard_rectangles.cmdSetDiscardRectangleEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetEvent',
-- 'Vulkan.Extensions.VK_NV_scissor_exclusive.cmdSetExclusiveScissorNV',
-- 'Vulkan.Extensions.VK_KHR_fragment_shading_rate.cmdSetFragmentShadingRateKHR',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetFrontFaceEXT',
-- 'Vulkan.Extensions.VK_EXT_line_rasterization.cmdSetLineStippleEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetLineWidth',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.cmdSetPerformanceMarkerINTEL',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.cmdSetPerformanceOverrideINTEL',
-- 'Vulkan.Extensions.VK_INTEL_performance_query.cmdSetPerformanceStreamMarkerINTEL',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetPrimitiveTopologyEXT',
-- 'Vulkan.Extensions.VK_EXT_sample_locations.cmdSetSampleLocationsEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetScissor',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetScissorWithCountEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetStencilCompareMask',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetStencilOpEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetStencilReference',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetStencilTestEnableEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetStencilWriteMask',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetViewport',
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdSetViewportShadingRatePaletteNV',
-- 'Vulkan.Extensions.VK_NV_clip_space_w_scaling.cmdSetViewportWScalingNV',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdSetViewportWithCountEXT',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdTraceRaysIndirectKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdTraceRaysKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdTraceRaysNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdUpdateBuffer',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdWaitEvents',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdWriteAccelerationStructuresPropertiesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdWriteAccelerationStructuresPropertiesNV',
-- 'Vulkan.Extensions.VK_AMD_buffer_marker.cmdWriteBufferMarkerAMD',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdWriteTimestamp',
-- 'Vulkan.Core10.CommandBuffer.endCommandBuffer',
-- 'Vulkan.Core10.CommandBuffer.freeCommandBuffers',
-- 'Vulkan.Core10.CommandBuffer.resetCommandBuffer'
data CommandBuffer = CommandBuffer
  { CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle :: Ptr CommandBuffer_T
  , CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
  }
  deriving stock (CommandBuffer -> CommandBuffer -> Bool
(CommandBuffer -> CommandBuffer -> Bool)
-> (CommandBuffer -> CommandBuffer -> Bool) -> Eq CommandBuffer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandBuffer -> CommandBuffer -> Bool
$c/= :: CommandBuffer -> CommandBuffer -> Bool
== :: CommandBuffer -> CommandBuffer -> Bool
$c== :: CommandBuffer -> CommandBuffer -> Bool
Eq, Int -> CommandBuffer -> ShowS
[CommandBuffer] -> ShowS
CommandBuffer -> String
(Int -> CommandBuffer -> ShowS)
-> (CommandBuffer -> String)
-> ([CommandBuffer] -> ShowS)
-> Show CommandBuffer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandBuffer] -> ShowS
$cshowList :: [CommandBuffer] -> ShowS
show :: CommandBuffer -> String
$cshow :: CommandBuffer -> String
showsPrec :: Int -> CommandBuffer -> ShowS
$cshowsPrec :: Int -> CommandBuffer -> ShowS
Show)
  deriving anyclass (Eq CommandBuffer
Zero CommandBuffer
(Eq CommandBuffer, Zero CommandBuffer) => IsHandle CommandBuffer
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero CommandBuffer
$cp1IsHandle :: Eq CommandBuffer
IsHandle)
instance Zero CommandBuffer where
  zero :: CommandBuffer
zero = Ptr CommandBuffer_T -> DeviceCmds -> CommandBuffer
CommandBuffer Ptr CommandBuffer_T
forall a. Zero a => a
zero DeviceCmds
forall a. Zero a => a
zero
instance HasObjectType CommandBuffer where
  objectTypeAndHandle :: CommandBuffer -> (ObjectType, Word64)
objectTypeAndHandle (CommandBuffer (Ptr CommandBuffer_T -> WordPtr
forall a. Ptr a -> WordPtr
ptrToWordPtr -> WordPtr h :: Word
h) _) = (ObjectType
OBJECT_TYPE_COMMAND_BUFFER, Word -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
h)


-- | VkDeviceMemory - Opaque handle to a device memory object
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.BindAccelerationStructureMemoryInfoKHR',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_bind_memory2.BindBufferMemoryInfo',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_bind_memory2.BindImageMemoryInfo',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.DeviceMemoryOpaqueCaptureAddressInfo',
-- 'Vulkan.Core10.Memory.MappedMemoryRange',
-- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.MemoryGetAndroidHardwareBufferInfoANDROID',
-- 'Vulkan.Extensions.VK_KHR_external_memory_fd.MemoryGetFdInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_memory_win32.MemoryGetWin32HandleInfoKHR',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageMemoryBind',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseMemoryBind',
-- 'Vulkan.Extensions.VK_KHR_win32_keyed_mutex.Win32KeyedMutexAcquireReleaseInfoKHR',
-- 'Vulkan.Extensions.VK_NV_win32_keyed_mutex.Win32KeyedMutexAcquireReleaseInfoNV',
-- 'Vulkan.Core10.Memory.allocateMemory',
-- 'Vulkan.Core10.MemoryManagement.bindBufferMemory',
-- 'Vulkan.Core10.MemoryManagement.bindImageMemory',
-- 'Vulkan.Core10.Memory.freeMemory',
-- 'Vulkan.Core10.Memory.getDeviceMemoryCommitment',
-- 'Vulkan.Extensions.VK_NV_external_memory_win32.getMemoryWin32HandleNV',
-- 'Vulkan.Core10.Memory.mapMemory', 'Vulkan.Core10.Memory.unmapMemory'
newtype DeviceMemory = DeviceMemory Word64
  deriving newtype (DeviceMemory -> DeviceMemory -> Bool
(DeviceMemory -> DeviceMemory -> Bool)
-> (DeviceMemory -> DeviceMemory -> Bool) -> Eq DeviceMemory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceMemory -> DeviceMemory -> Bool
$c/= :: DeviceMemory -> DeviceMemory -> Bool
== :: DeviceMemory -> DeviceMemory -> Bool
$c== :: DeviceMemory -> DeviceMemory -> Bool
Eq, Eq DeviceMemory
Eq DeviceMemory =>
(DeviceMemory -> DeviceMemory -> Ordering)
-> (DeviceMemory -> DeviceMemory -> Bool)
-> (DeviceMemory -> DeviceMemory -> Bool)
-> (DeviceMemory -> DeviceMemory -> Bool)
-> (DeviceMemory -> DeviceMemory -> Bool)
-> (DeviceMemory -> DeviceMemory -> DeviceMemory)
-> (DeviceMemory -> DeviceMemory -> DeviceMemory)
-> Ord DeviceMemory
DeviceMemory -> DeviceMemory -> Bool
DeviceMemory -> DeviceMemory -> Ordering
DeviceMemory -> DeviceMemory -> DeviceMemory
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 :: DeviceMemory -> DeviceMemory -> DeviceMemory
$cmin :: DeviceMemory -> DeviceMemory -> DeviceMemory
max :: DeviceMemory -> DeviceMemory -> DeviceMemory
$cmax :: DeviceMemory -> DeviceMemory -> DeviceMemory
>= :: DeviceMemory -> DeviceMemory -> Bool
$c>= :: DeviceMemory -> DeviceMemory -> Bool
> :: DeviceMemory -> DeviceMemory -> Bool
$c> :: DeviceMemory -> DeviceMemory -> Bool
<= :: DeviceMemory -> DeviceMemory -> Bool
$c<= :: DeviceMemory -> DeviceMemory -> Bool
< :: DeviceMemory -> DeviceMemory -> Bool
$c< :: DeviceMemory -> DeviceMemory -> Bool
compare :: DeviceMemory -> DeviceMemory -> Ordering
$ccompare :: DeviceMemory -> DeviceMemory -> Ordering
$cp1Ord :: Eq DeviceMemory
Ord, Ptr b -> Int -> IO DeviceMemory
Ptr b -> Int -> DeviceMemory -> IO ()
Ptr DeviceMemory -> IO DeviceMemory
Ptr DeviceMemory -> Int -> IO DeviceMemory
Ptr DeviceMemory -> Int -> DeviceMemory -> IO ()
Ptr DeviceMemory -> DeviceMemory -> IO ()
DeviceMemory -> Int
(DeviceMemory -> Int)
-> (DeviceMemory -> Int)
-> (Ptr DeviceMemory -> Int -> IO DeviceMemory)
-> (Ptr DeviceMemory -> Int -> DeviceMemory -> IO ())
-> (forall b. Ptr b -> Int -> IO DeviceMemory)
-> (forall b. Ptr b -> Int -> DeviceMemory -> IO ())
-> (Ptr DeviceMemory -> IO DeviceMemory)
-> (Ptr DeviceMemory -> DeviceMemory -> IO ())
-> Storable DeviceMemory
forall b. Ptr b -> Int -> IO DeviceMemory
forall b. Ptr b -> Int -> DeviceMemory -> 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 DeviceMemory -> DeviceMemory -> IO ()
$cpoke :: Ptr DeviceMemory -> DeviceMemory -> IO ()
peek :: Ptr DeviceMemory -> IO DeviceMemory
$cpeek :: Ptr DeviceMemory -> IO DeviceMemory
pokeByteOff :: Ptr b -> Int -> DeviceMemory -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DeviceMemory -> IO ()
peekByteOff :: Ptr b -> Int -> IO DeviceMemory
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DeviceMemory
pokeElemOff :: Ptr DeviceMemory -> Int -> DeviceMemory -> IO ()
$cpokeElemOff :: Ptr DeviceMemory -> Int -> DeviceMemory -> IO ()
peekElemOff :: Ptr DeviceMemory -> Int -> IO DeviceMemory
$cpeekElemOff :: Ptr DeviceMemory -> Int -> IO DeviceMemory
alignment :: DeviceMemory -> Int
$calignment :: DeviceMemory -> Int
sizeOf :: DeviceMemory -> Int
$csizeOf :: DeviceMemory -> Int
Storable, DeviceMemory
DeviceMemory -> Zero DeviceMemory
forall a. a -> Zero a
zero :: DeviceMemory
$czero :: DeviceMemory
Zero)
  deriving anyclass (Eq DeviceMemory
Zero DeviceMemory
(Eq DeviceMemory, Zero DeviceMemory) => IsHandle DeviceMemory
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DeviceMemory
$cp1IsHandle :: Eq DeviceMemory
IsHandle)
instance HasObjectType DeviceMemory where
  objectTypeAndHandle :: DeviceMemory -> (ObjectType, Word64)
objectTypeAndHandle (DeviceMemory h :: Word64
h) = (ObjectType
OBJECT_TYPE_DEVICE_MEMORY, Word64
h)
instance Show DeviceMemory where
  showsPrec :: Int -> DeviceMemory -> ShowS
showsPrec p :: Int
p (DeviceMemory x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DeviceMemory 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)


-- | VkCommandPool - Opaque handle to a command pool object
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBuffer.CommandBufferAllocateInfo',
-- 'Vulkan.Core10.CommandPool.createCommandPool',
-- 'Vulkan.Core10.CommandPool.destroyCommandPool',
-- 'Vulkan.Core10.CommandBuffer.freeCommandBuffers',
-- 'Vulkan.Core10.CommandPool.resetCommandPool',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance1.trimCommandPool',
-- 'Vulkan.Extensions.VK_KHR_maintenance1.trimCommandPoolKHR'
newtype CommandPool = CommandPool Word64
  deriving newtype (CommandPool -> CommandPool -> Bool
(CommandPool -> CommandPool -> Bool)
-> (CommandPool -> CommandPool -> Bool) -> Eq CommandPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandPool -> CommandPool -> Bool
$c/= :: CommandPool -> CommandPool -> Bool
== :: CommandPool -> CommandPool -> Bool
$c== :: CommandPool -> CommandPool -> Bool
Eq, Eq CommandPool
Eq CommandPool =>
(CommandPool -> CommandPool -> Ordering)
-> (CommandPool -> CommandPool -> Bool)
-> (CommandPool -> CommandPool -> Bool)
-> (CommandPool -> CommandPool -> Bool)
-> (CommandPool -> CommandPool -> Bool)
-> (CommandPool -> CommandPool -> CommandPool)
-> (CommandPool -> CommandPool -> CommandPool)
-> Ord CommandPool
CommandPool -> CommandPool -> Bool
CommandPool -> CommandPool -> Ordering
CommandPool -> CommandPool -> CommandPool
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 :: CommandPool -> CommandPool -> CommandPool
$cmin :: CommandPool -> CommandPool -> CommandPool
max :: CommandPool -> CommandPool -> CommandPool
$cmax :: CommandPool -> CommandPool -> CommandPool
>= :: CommandPool -> CommandPool -> Bool
$c>= :: CommandPool -> CommandPool -> Bool
> :: CommandPool -> CommandPool -> Bool
$c> :: CommandPool -> CommandPool -> Bool
<= :: CommandPool -> CommandPool -> Bool
$c<= :: CommandPool -> CommandPool -> Bool
< :: CommandPool -> CommandPool -> Bool
$c< :: CommandPool -> CommandPool -> Bool
compare :: CommandPool -> CommandPool -> Ordering
$ccompare :: CommandPool -> CommandPool -> Ordering
$cp1Ord :: Eq CommandPool
Ord, Ptr b -> Int -> IO CommandPool
Ptr b -> Int -> CommandPool -> IO ()
Ptr CommandPool -> IO CommandPool
Ptr CommandPool -> Int -> IO CommandPool
Ptr CommandPool -> Int -> CommandPool -> IO ()
Ptr CommandPool -> CommandPool -> IO ()
CommandPool -> Int
(CommandPool -> Int)
-> (CommandPool -> Int)
-> (Ptr CommandPool -> Int -> IO CommandPool)
-> (Ptr CommandPool -> Int -> CommandPool -> IO ())
-> (forall b. Ptr b -> Int -> IO CommandPool)
-> (forall b. Ptr b -> Int -> CommandPool -> IO ())
-> (Ptr CommandPool -> IO CommandPool)
-> (Ptr CommandPool -> CommandPool -> IO ())
-> Storable CommandPool
forall b. Ptr b -> Int -> IO CommandPool
forall b. Ptr b -> Int -> CommandPool -> 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 CommandPool -> CommandPool -> IO ()
$cpoke :: Ptr CommandPool -> CommandPool -> IO ()
peek :: Ptr CommandPool -> IO CommandPool
$cpeek :: Ptr CommandPool -> IO CommandPool
pokeByteOff :: Ptr b -> Int -> CommandPool -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CommandPool -> IO ()
peekByteOff :: Ptr b -> Int -> IO CommandPool
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CommandPool
pokeElemOff :: Ptr CommandPool -> Int -> CommandPool -> IO ()
$cpokeElemOff :: Ptr CommandPool -> Int -> CommandPool -> IO ()
peekElemOff :: Ptr CommandPool -> Int -> IO CommandPool
$cpeekElemOff :: Ptr CommandPool -> Int -> IO CommandPool
alignment :: CommandPool -> Int
$calignment :: CommandPool -> Int
sizeOf :: CommandPool -> Int
$csizeOf :: CommandPool -> Int
Storable, CommandPool
CommandPool -> Zero CommandPool
forall a. a -> Zero a
zero :: CommandPool
$czero :: CommandPool
Zero)
  deriving anyclass (Eq CommandPool
Zero CommandPool
(Eq CommandPool, Zero CommandPool) => IsHandle CommandPool
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero CommandPool
$cp1IsHandle :: Eq CommandPool
IsHandle)
instance HasObjectType CommandPool where
  objectTypeAndHandle :: CommandPool -> (ObjectType, Word64)
objectTypeAndHandle (CommandPool h :: Word64
h) = (ObjectType
OBJECT_TYPE_COMMAND_POOL, Word64
h)
instance Show CommandPool where
  showsPrec :: Int -> CommandPool -> ShowS
showsPrec p :: Int
p (CommandPool x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "CommandPool 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)


-- | VkBuffer - Opaque handle to a buffer object
--
-- = See Also
--
-- 'Vulkan.Core11.Promoted_From_VK_KHR_bind_memory2.BindBufferMemoryInfo',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.BufferDeviceAddressInfo',
-- 'Vulkan.Core10.OtherTypes.BufferMemoryBarrier',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.BufferMemoryRequirementsInfo2',
-- 'Vulkan.Core10.BufferView.BufferViewCreateInfo',
-- 'Vulkan.Extensions.VK_EXT_conditional_rendering.ConditionalRenderingBeginInfoEXT',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.CopyBufferInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.CopyBufferToImageInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.CopyImageToBufferInfo2KHR',
-- 'Vulkan.Extensions.VK_NV_dedicated_allocation.DedicatedAllocationMemoryAllocateInfoNV',
-- 'Vulkan.Core10.DescriptorSet.DescriptorBufferInfo',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.GeneratedCommandsInfoNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.GeometryAABBNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.GeometryTrianglesNV',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.IndirectCommandsStreamNV',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseBufferMemoryBindInfo',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.StridedBufferRegionKHR',
-- 'Vulkan.Core10.MemoryManagement.bindBufferMemory',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdBeginTransformFeedbackEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBindIndexBuffer',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdBindTransformFeedbackBuffersEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBindVertexBuffers',
-- 'Vulkan.Extensions.VK_EXT_extended_dynamic_state.cmdBindVertexBuffers2EXT',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdBuildAccelerationStructureIndirectKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdBuildAccelerationStructureNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyBuffer',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyBufferToImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyImageToBuffer',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyQueryPoolResults',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDispatchIndirect',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndexedIndirect',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_draw_indirect_count.cmdDrawIndexedIndirectCount',
-- 'Vulkan.Extensions.VK_AMD_draw_indirect_count.cmdDrawIndexedIndirectCountAMD',
-- 'Vulkan.Extensions.VK_KHR_draw_indirect_count.cmdDrawIndexedIndirectCountKHR',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdDrawIndirect',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdDrawIndirectByteCountEXT',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_draw_indirect_count.cmdDrawIndirectCount',
-- 'Vulkan.Extensions.VK_AMD_draw_indirect_count.cmdDrawIndirectCountAMD',
-- 'Vulkan.Extensions.VK_KHR_draw_indirect_count.cmdDrawIndirectCountKHR',
-- 'Vulkan.Extensions.VK_NV_mesh_shader.cmdDrawMeshTasksIndirectCountNV',
-- 'Vulkan.Extensions.VK_NV_mesh_shader.cmdDrawMeshTasksIndirectNV',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndTransformFeedbackEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdFillBuffer',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdTraceRaysIndirectKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdTraceRaysNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdUpdateBuffer',
-- 'Vulkan.Extensions.VK_AMD_buffer_marker.cmdWriteBufferMarkerAMD',
-- 'Vulkan.Core10.Buffer.createBuffer',
-- 'Vulkan.Core10.Buffer.destroyBuffer',
-- 'Vulkan.Core10.MemoryManagement.getBufferMemoryRequirements'
newtype Buffer = Buffer Word64
  deriving newtype (Buffer -> Buffer -> Bool
(Buffer -> Buffer -> Bool)
-> (Buffer -> Buffer -> Bool) -> Eq Buffer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Buffer -> Buffer -> Bool
$c/= :: Buffer -> Buffer -> Bool
== :: Buffer -> Buffer -> Bool
$c== :: Buffer -> Buffer -> Bool
Eq, Eq Buffer
Eq Buffer =>
(Buffer -> Buffer -> Ordering)
-> (Buffer -> Buffer -> Bool)
-> (Buffer -> Buffer -> Bool)
-> (Buffer -> Buffer -> Bool)
-> (Buffer -> Buffer -> Bool)
-> (Buffer -> Buffer -> Buffer)
-> (Buffer -> Buffer -> Buffer)
-> Ord Buffer
Buffer -> Buffer -> Bool
Buffer -> Buffer -> Ordering
Buffer -> Buffer -> Buffer
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 :: Buffer -> Buffer -> Buffer
$cmin :: Buffer -> Buffer -> Buffer
max :: Buffer -> Buffer -> Buffer
$cmax :: Buffer -> Buffer -> Buffer
>= :: Buffer -> Buffer -> Bool
$c>= :: Buffer -> Buffer -> Bool
> :: Buffer -> Buffer -> Bool
$c> :: Buffer -> Buffer -> Bool
<= :: Buffer -> Buffer -> Bool
$c<= :: Buffer -> Buffer -> Bool
< :: Buffer -> Buffer -> Bool
$c< :: Buffer -> Buffer -> Bool
compare :: Buffer -> Buffer -> Ordering
$ccompare :: Buffer -> Buffer -> Ordering
$cp1Ord :: Eq Buffer
Ord, Ptr b -> Int -> IO Buffer
Ptr b -> Int -> Buffer -> IO ()
Ptr Buffer -> IO Buffer
Ptr Buffer -> Int -> IO Buffer
Ptr Buffer -> Int -> Buffer -> IO ()
Ptr Buffer -> Buffer -> IO ()
Buffer -> Int
(Buffer -> Int)
-> (Buffer -> Int)
-> (Ptr Buffer -> Int -> IO Buffer)
-> (Ptr Buffer -> Int -> Buffer -> IO ())
-> (forall b. Ptr b -> Int -> IO Buffer)
-> (forall b. Ptr b -> Int -> Buffer -> IO ())
-> (Ptr Buffer -> IO Buffer)
-> (Ptr Buffer -> Buffer -> IO ())
-> Storable Buffer
forall b. Ptr b -> Int -> IO Buffer
forall b. Ptr b -> Int -> Buffer -> 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 Buffer -> Buffer -> IO ()
$cpoke :: Ptr Buffer -> Buffer -> IO ()
peek :: Ptr Buffer -> IO Buffer
$cpeek :: Ptr Buffer -> IO Buffer
pokeByteOff :: Ptr b -> Int -> Buffer -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Buffer -> IO ()
peekByteOff :: Ptr b -> Int -> IO Buffer
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Buffer
pokeElemOff :: Ptr Buffer -> Int -> Buffer -> IO ()
$cpokeElemOff :: Ptr Buffer -> Int -> Buffer -> IO ()
peekElemOff :: Ptr Buffer -> Int -> IO Buffer
$cpeekElemOff :: Ptr Buffer -> Int -> IO Buffer
alignment :: Buffer -> Int
$calignment :: Buffer -> Int
sizeOf :: Buffer -> Int
$csizeOf :: Buffer -> Int
Storable, Buffer
Buffer -> Zero Buffer
forall a. a -> Zero a
zero :: Buffer
$czero :: Buffer
Zero)
  deriving anyclass (Eq Buffer
Zero Buffer
(Eq Buffer, Zero Buffer) => IsHandle Buffer
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Buffer
$cp1IsHandle :: Eq Buffer
IsHandle)
instance HasObjectType Buffer where
  objectTypeAndHandle :: Buffer -> (ObjectType, Word64)
objectTypeAndHandle (Buffer h :: Word64
h) = (ObjectType
OBJECT_TYPE_BUFFER, Word64
h)
instance Show Buffer where
  showsPrec :: Int -> Buffer -> ShowS
showsPrec p :: Int
p (Buffer x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Buffer 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)


-- | VkBufferView - Opaque handle to a buffer view object
--
-- = See Also
--
-- 'Vulkan.Core10.DescriptorSet.WriteDescriptorSet',
-- 'Vulkan.Core10.BufferView.createBufferView',
-- 'Vulkan.Core10.BufferView.destroyBufferView'
newtype BufferView = BufferView Word64
  deriving newtype (BufferView -> BufferView -> Bool
(BufferView -> BufferView -> Bool)
-> (BufferView -> BufferView -> Bool) -> Eq BufferView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BufferView -> BufferView -> Bool
$c/= :: BufferView -> BufferView -> Bool
== :: BufferView -> BufferView -> Bool
$c== :: BufferView -> BufferView -> Bool
Eq, Eq BufferView
Eq BufferView =>
(BufferView -> BufferView -> Ordering)
-> (BufferView -> BufferView -> Bool)
-> (BufferView -> BufferView -> Bool)
-> (BufferView -> BufferView -> Bool)
-> (BufferView -> BufferView -> Bool)
-> (BufferView -> BufferView -> BufferView)
-> (BufferView -> BufferView -> BufferView)
-> Ord BufferView
BufferView -> BufferView -> Bool
BufferView -> BufferView -> Ordering
BufferView -> BufferView -> BufferView
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 :: BufferView -> BufferView -> BufferView
$cmin :: BufferView -> BufferView -> BufferView
max :: BufferView -> BufferView -> BufferView
$cmax :: BufferView -> BufferView -> BufferView
>= :: BufferView -> BufferView -> Bool
$c>= :: BufferView -> BufferView -> Bool
> :: BufferView -> BufferView -> Bool
$c> :: BufferView -> BufferView -> Bool
<= :: BufferView -> BufferView -> Bool
$c<= :: BufferView -> BufferView -> Bool
< :: BufferView -> BufferView -> Bool
$c< :: BufferView -> BufferView -> Bool
compare :: BufferView -> BufferView -> Ordering
$ccompare :: BufferView -> BufferView -> Ordering
$cp1Ord :: Eq BufferView
Ord, Ptr b -> Int -> IO BufferView
Ptr b -> Int -> BufferView -> IO ()
Ptr BufferView -> IO BufferView
Ptr BufferView -> Int -> IO BufferView
Ptr BufferView -> Int -> BufferView -> IO ()
Ptr BufferView -> BufferView -> IO ()
BufferView -> Int
(BufferView -> Int)
-> (BufferView -> Int)
-> (Ptr BufferView -> Int -> IO BufferView)
-> (Ptr BufferView -> Int -> BufferView -> IO ())
-> (forall b. Ptr b -> Int -> IO BufferView)
-> (forall b. Ptr b -> Int -> BufferView -> IO ())
-> (Ptr BufferView -> IO BufferView)
-> (Ptr BufferView -> BufferView -> IO ())
-> Storable BufferView
forall b. Ptr b -> Int -> IO BufferView
forall b. Ptr b -> Int -> BufferView -> 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 BufferView -> BufferView -> IO ()
$cpoke :: Ptr BufferView -> BufferView -> IO ()
peek :: Ptr BufferView -> IO BufferView
$cpeek :: Ptr BufferView -> IO BufferView
pokeByteOff :: Ptr b -> Int -> BufferView -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> BufferView -> IO ()
peekByteOff :: Ptr b -> Int -> IO BufferView
$cpeekByteOff :: forall b. Ptr b -> Int -> IO BufferView
pokeElemOff :: Ptr BufferView -> Int -> BufferView -> IO ()
$cpokeElemOff :: Ptr BufferView -> Int -> BufferView -> IO ()
peekElemOff :: Ptr BufferView -> Int -> IO BufferView
$cpeekElemOff :: Ptr BufferView -> Int -> IO BufferView
alignment :: BufferView -> Int
$calignment :: BufferView -> Int
sizeOf :: BufferView -> Int
$csizeOf :: BufferView -> Int
Storable, BufferView
BufferView -> Zero BufferView
forall a. a -> Zero a
zero :: BufferView
$czero :: BufferView
Zero)
  deriving anyclass (Eq BufferView
Zero BufferView
(Eq BufferView, Zero BufferView) => IsHandle BufferView
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero BufferView
$cp1IsHandle :: Eq BufferView
IsHandle)
instance HasObjectType BufferView where
  objectTypeAndHandle :: BufferView -> (ObjectType, Word64)
objectTypeAndHandle (BufferView h :: Word64
h) = (ObjectType
OBJECT_TYPE_BUFFER_VIEW, Word64
h)
instance Show BufferView where
  showsPrec :: Int -> BufferView -> ShowS
showsPrec p :: Int
p (BufferView x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "BufferView 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)


-- | VkImage - Opaque handle to an image object
--
-- = See Also
--
-- 'Vulkan.Core11.Promoted_From_VK_KHR_bind_memory2.BindImageMemoryInfo',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.BlitImageInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.CopyBufferToImageInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.CopyImageInfo2KHR',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.CopyImageToBufferInfo2KHR',
-- 'Vulkan.Extensions.VK_NV_dedicated_allocation.DedicatedAllocationMemoryAllocateInfoNV',
-- 'Vulkan.Core10.OtherTypes.ImageMemoryBarrier',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.ImageMemoryRequirementsInfo2',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.ImageSparseMemoryRequirementsInfo2',
-- 'Vulkan.Core10.ImageView.ImageViewCreateInfo',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo',
-- 'Vulkan.Extensions.VK_KHR_copy_commands2.ResolveImageInfo2KHR',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageMemoryBindInfo',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageOpaqueMemoryBindInfo',
-- 'Vulkan.Core10.MemoryManagement.bindImageMemory',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBlitImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearColorImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdClearDepthStencilImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyBufferToImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyImage',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyImageToBuffer',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdResolveImage',
-- 'Vulkan.Core10.Image.createImage', 'Vulkan.Core10.Image.destroyImage',
-- 'Vulkan.Extensions.VK_EXT_image_drm_format_modifier.getImageDrmFormatModifierPropertiesEXT',
-- 'Vulkan.Core10.MemoryManagement.getImageMemoryRequirements',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.getImageSparseMemoryRequirements',
-- 'Vulkan.Core10.Image.getImageSubresourceLayout',
-- 'Vulkan.Extensions.VK_KHR_swapchain.getSwapchainImagesKHR'
newtype Image = Image Word64
  deriving newtype (Image -> Image -> Bool
(Image -> Image -> Bool) -> (Image -> Image -> Bool) -> Eq Image
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Image -> Image -> Bool
$c/= :: Image -> Image -> Bool
== :: Image -> Image -> Bool
$c== :: Image -> Image -> Bool
Eq, Eq Image
Eq Image =>
(Image -> Image -> Ordering)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Bool)
-> (Image -> Image -> Image)
-> (Image -> Image -> Image)
-> Ord Image
Image -> Image -> Bool
Image -> Image -> Ordering
Image -> Image -> Image
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 :: Image -> Image -> Image
$cmin :: Image -> Image -> Image
max :: Image -> Image -> Image
$cmax :: Image -> Image -> Image
>= :: Image -> Image -> Bool
$c>= :: Image -> Image -> Bool
> :: Image -> Image -> Bool
$c> :: Image -> Image -> Bool
<= :: Image -> Image -> Bool
$c<= :: Image -> Image -> Bool
< :: Image -> Image -> Bool
$c< :: Image -> Image -> Bool
compare :: Image -> Image -> Ordering
$ccompare :: Image -> Image -> Ordering
$cp1Ord :: Eq Image
Ord, Ptr b -> Int -> IO Image
Ptr b -> Int -> Image -> IO ()
Ptr Image -> IO Image
Ptr Image -> Int -> IO Image
Ptr Image -> Int -> Image -> IO ()
Ptr Image -> Image -> IO ()
Image -> Int
(Image -> Int)
-> (Image -> Int)
-> (Ptr Image -> Int -> IO Image)
-> (Ptr Image -> Int -> Image -> IO ())
-> (forall b. Ptr b -> Int -> IO Image)
-> (forall b. Ptr b -> Int -> Image -> IO ())
-> (Ptr Image -> IO Image)
-> (Ptr Image -> Image -> IO ())
-> Storable Image
forall b. Ptr b -> Int -> IO Image
forall b. Ptr b -> Int -> Image -> 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 Image -> Image -> IO ()
$cpoke :: Ptr Image -> Image -> IO ()
peek :: Ptr Image -> IO Image
$cpeek :: Ptr Image -> IO Image
pokeByteOff :: Ptr b -> Int -> Image -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Image -> IO ()
peekByteOff :: Ptr b -> Int -> IO Image
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Image
pokeElemOff :: Ptr Image -> Int -> Image -> IO ()
$cpokeElemOff :: Ptr Image -> Int -> Image -> IO ()
peekElemOff :: Ptr Image -> Int -> IO Image
$cpeekElemOff :: Ptr Image -> Int -> IO Image
alignment :: Image -> Int
$calignment :: Image -> Int
sizeOf :: Image -> Int
$csizeOf :: Image -> Int
Storable, Image
Image -> Zero Image
forall a. a -> Zero a
zero :: Image
$czero :: Image
Zero)
  deriving anyclass (Eq Image
Zero Image
(Eq Image, Zero Image) => IsHandle Image
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Image
$cp1IsHandle :: Eq Image
IsHandle)
instance HasObjectType Image where
  objectTypeAndHandle :: Image -> (ObjectType, Word64)
objectTypeAndHandle (Image h :: Word64
h) = (ObjectType
OBJECT_TYPE_IMAGE, Word64
h)
instance Show Image where
  showsPrec :: Int -> Image -> ShowS
showsPrec p :: Int
p (Image x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Image 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)


-- | VkImageView - Opaque handle to an image view object
--
-- = See Also
--
-- 'Vulkan.Core10.DescriptorSet.DescriptorImageInfo',
-- 'Vulkan.Core10.Pass.FramebufferCreateInfo',
-- 'Vulkan.Extensions.VK_NVX_image_view_handle.ImageViewHandleInfoNVX',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.RenderPassAttachmentBeginInfo',
-- 'Vulkan.Extensions.VK_NV_shading_rate_image.cmdBindShadingRateImageNV',
-- 'Vulkan.Core10.ImageView.createImageView',
-- 'Vulkan.Core10.ImageView.destroyImageView',
-- 'Vulkan.Extensions.VK_NVX_image_view_handle.getImageViewAddressNVX'
newtype ImageView = ImageView Word64
  deriving newtype (ImageView -> ImageView -> Bool
(ImageView -> ImageView -> Bool)
-> (ImageView -> ImageView -> Bool) -> Eq ImageView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImageView -> ImageView -> Bool
$c/= :: ImageView -> ImageView -> Bool
== :: ImageView -> ImageView -> Bool
$c== :: ImageView -> ImageView -> Bool
Eq, Eq ImageView
Eq ImageView =>
(ImageView -> ImageView -> Ordering)
-> (ImageView -> ImageView -> Bool)
-> (ImageView -> ImageView -> Bool)
-> (ImageView -> ImageView -> Bool)
-> (ImageView -> ImageView -> Bool)
-> (ImageView -> ImageView -> ImageView)
-> (ImageView -> ImageView -> ImageView)
-> Ord ImageView
ImageView -> ImageView -> Bool
ImageView -> ImageView -> Ordering
ImageView -> ImageView -> ImageView
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 :: ImageView -> ImageView -> ImageView
$cmin :: ImageView -> ImageView -> ImageView
max :: ImageView -> ImageView -> ImageView
$cmax :: ImageView -> ImageView -> ImageView
>= :: ImageView -> ImageView -> Bool
$c>= :: ImageView -> ImageView -> Bool
> :: ImageView -> ImageView -> Bool
$c> :: ImageView -> ImageView -> Bool
<= :: ImageView -> ImageView -> Bool
$c<= :: ImageView -> ImageView -> Bool
< :: ImageView -> ImageView -> Bool
$c< :: ImageView -> ImageView -> Bool
compare :: ImageView -> ImageView -> Ordering
$ccompare :: ImageView -> ImageView -> Ordering
$cp1Ord :: Eq ImageView
Ord, Ptr b -> Int -> IO ImageView
Ptr b -> Int -> ImageView -> IO ()
Ptr ImageView -> IO ImageView
Ptr ImageView -> Int -> IO ImageView
Ptr ImageView -> Int -> ImageView -> IO ()
Ptr ImageView -> ImageView -> IO ()
ImageView -> Int
(ImageView -> Int)
-> (ImageView -> Int)
-> (Ptr ImageView -> Int -> IO ImageView)
-> (Ptr ImageView -> Int -> ImageView -> IO ())
-> (forall b. Ptr b -> Int -> IO ImageView)
-> (forall b. Ptr b -> Int -> ImageView -> IO ())
-> (Ptr ImageView -> IO ImageView)
-> (Ptr ImageView -> ImageView -> IO ())
-> Storable ImageView
forall b. Ptr b -> Int -> IO ImageView
forall b. Ptr b -> Int -> ImageView -> 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 ImageView -> ImageView -> IO ()
$cpoke :: Ptr ImageView -> ImageView -> IO ()
peek :: Ptr ImageView -> IO ImageView
$cpeek :: Ptr ImageView -> IO ImageView
pokeByteOff :: Ptr b -> Int -> ImageView -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ImageView -> IO ()
peekByteOff :: Ptr b -> Int -> IO ImageView
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ImageView
pokeElemOff :: Ptr ImageView -> Int -> ImageView -> IO ()
$cpokeElemOff :: Ptr ImageView -> Int -> ImageView -> IO ()
peekElemOff :: Ptr ImageView -> Int -> IO ImageView
$cpeekElemOff :: Ptr ImageView -> Int -> IO ImageView
alignment :: ImageView -> Int
$calignment :: ImageView -> Int
sizeOf :: ImageView -> Int
$csizeOf :: ImageView -> Int
Storable, ImageView
ImageView -> Zero ImageView
forall a. a -> Zero a
zero :: ImageView
$czero :: ImageView
Zero)
  deriving anyclass (Eq ImageView
Zero ImageView
(Eq ImageView, Zero ImageView) => IsHandle ImageView
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero ImageView
$cp1IsHandle :: Eq ImageView
IsHandle)
instance HasObjectType ImageView where
  objectTypeAndHandle :: ImageView -> (ObjectType, Word64)
objectTypeAndHandle (ImageView h :: Word64
h) = (ObjectType
OBJECT_TYPE_IMAGE_VIEW, Word64
h)
instance Show ImageView where
  showsPrec :: Int -> ImageView -> ShowS
showsPrec p :: Int
p (ImageView x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "ImageView 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)


-- | VkShaderModule - Opaque handle to a shader module object
--
-- = See Also
--
-- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo',
-- 'Vulkan.Core10.Shader.createShaderModule',
-- 'Vulkan.Core10.Shader.destroyShaderModule'
newtype ShaderModule = ShaderModule Word64
  deriving newtype (ShaderModule -> ShaderModule -> Bool
(ShaderModule -> ShaderModule -> Bool)
-> (ShaderModule -> ShaderModule -> Bool) -> Eq ShaderModule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShaderModule -> ShaderModule -> Bool
$c/= :: ShaderModule -> ShaderModule -> Bool
== :: ShaderModule -> ShaderModule -> Bool
$c== :: ShaderModule -> ShaderModule -> Bool
Eq, Eq ShaderModule
Eq ShaderModule =>
(ShaderModule -> ShaderModule -> Ordering)
-> (ShaderModule -> ShaderModule -> Bool)
-> (ShaderModule -> ShaderModule -> Bool)
-> (ShaderModule -> ShaderModule -> Bool)
-> (ShaderModule -> ShaderModule -> Bool)
-> (ShaderModule -> ShaderModule -> ShaderModule)
-> (ShaderModule -> ShaderModule -> ShaderModule)
-> Ord ShaderModule
ShaderModule -> ShaderModule -> Bool
ShaderModule -> ShaderModule -> Ordering
ShaderModule -> ShaderModule -> ShaderModule
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 :: ShaderModule -> ShaderModule -> ShaderModule
$cmin :: ShaderModule -> ShaderModule -> ShaderModule
max :: ShaderModule -> ShaderModule -> ShaderModule
$cmax :: ShaderModule -> ShaderModule -> ShaderModule
>= :: ShaderModule -> ShaderModule -> Bool
$c>= :: ShaderModule -> ShaderModule -> Bool
> :: ShaderModule -> ShaderModule -> Bool
$c> :: ShaderModule -> ShaderModule -> Bool
<= :: ShaderModule -> ShaderModule -> Bool
$c<= :: ShaderModule -> ShaderModule -> Bool
< :: ShaderModule -> ShaderModule -> Bool
$c< :: ShaderModule -> ShaderModule -> Bool
compare :: ShaderModule -> ShaderModule -> Ordering
$ccompare :: ShaderModule -> ShaderModule -> Ordering
$cp1Ord :: Eq ShaderModule
Ord, Ptr b -> Int -> IO ShaderModule
Ptr b -> Int -> ShaderModule -> IO ()
Ptr ShaderModule -> IO ShaderModule
Ptr ShaderModule -> Int -> IO ShaderModule
Ptr ShaderModule -> Int -> ShaderModule -> IO ()
Ptr ShaderModule -> ShaderModule -> IO ()
ShaderModule -> Int
(ShaderModule -> Int)
-> (ShaderModule -> Int)
-> (Ptr ShaderModule -> Int -> IO ShaderModule)
-> (Ptr ShaderModule -> Int -> ShaderModule -> IO ())
-> (forall b. Ptr b -> Int -> IO ShaderModule)
-> (forall b. Ptr b -> Int -> ShaderModule -> IO ())
-> (Ptr ShaderModule -> IO ShaderModule)
-> (Ptr ShaderModule -> ShaderModule -> IO ())
-> Storable ShaderModule
forall b. Ptr b -> Int -> IO ShaderModule
forall b. Ptr b -> Int -> ShaderModule -> 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 ShaderModule -> ShaderModule -> IO ()
$cpoke :: Ptr ShaderModule -> ShaderModule -> IO ()
peek :: Ptr ShaderModule -> IO ShaderModule
$cpeek :: Ptr ShaderModule -> IO ShaderModule
pokeByteOff :: Ptr b -> Int -> ShaderModule -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ShaderModule -> IO ()
peekByteOff :: Ptr b -> Int -> IO ShaderModule
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ShaderModule
pokeElemOff :: Ptr ShaderModule -> Int -> ShaderModule -> IO ()
$cpokeElemOff :: Ptr ShaderModule -> Int -> ShaderModule -> IO ()
peekElemOff :: Ptr ShaderModule -> Int -> IO ShaderModule
$cpeekElemOff :: Ptr ShaderModule -> Int -> IO ShaderModule
alignment :: ShaderModule -> Int
$calignment :: ShaderModule -> Int
sizeOf :: ShaderModule -> Int
$csizeOf :: ShaderModule -> Int
Storable, ShaderModule
ShaderModule -> Zero ShaderModule
forall a. a -> Zero a
zero :: ShaderModule
$czero :: ShaderModule
Zero)
  deriving anyclass (Eq ShaderModule
Zero ShaderModule
(Eq ShaderModule, Zero ShaderModule) => IsHandle ShaderModule
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero ShaderModule
$cp1IsHandle :: Eq ShaderModule
IsHandle)
instance HasObjectType ShaderModule where
  objectTypeAndHandle :: ShaderModule -> (ObjectType, Word64)
objectTypeAndHandle (ShaderModule h :: Word64
h) = (ObjectType
OBJECT_TYPE_SHADER_MODULE, Word64
h)
instance Show ShaderModule where
  showsPrec :: Int -> ShaderModule -> ShowS
showsPrec p :: Int
p (ShaderModule x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "ShaderModule 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)


-- | VkPipeline - Opaque handle to a pipeline object
--
-- = See Also
--
-- 'Vulkan.Core10.Pipeline.ComputePipelineCreateInfo',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.GeneratedCommandsInfoNV',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.GeneratedCommandsMemoryRequirementsInfoNV',
-- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.GraphicsPipelineShaderGroupsCreateInfoNV',
-- 'Vulkan.Extensions.VK_KHR_pipeline_executable_properties.PipelineExecutableInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_pipeline_executable_properties.PipelineInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_pipeline_library.PipelineLibraryCreateInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.RayTracingPipelineCreateInfoKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.RayTracingPipelineCreateInfoNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBindPipeline',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.cmdBindPipelineShaderGroupNV',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.compileDeferredNV',
-- 'Vulkan.Core10.Pipeline.createComputePipelines',
-- 'Vulkan.Core10.Pipeline.createGraphicsPipelines',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.createRayTracingPipelinesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.createRayTracingPipelinesNV',
-- 'Vulkan.Core10.Pipeline.destroyPipeline',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.getRayTracingCaptureReplayShaderGroupHandlesKHR',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.getRayTracingShaderGroupHandlesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.getRayTracingShaderGroupHandlesNV',
-- 'Vulkan.Extensions.VK_AMD_shader_info.getShaderInfoAMD'
newtype Pipeline = Pipeline Word64
  deriving newtype (Pipeline -> Pipeline -> Bool
(Pipeline -> Pipeline -> Bool)
-> (Pipeline -> Pipeline -> Bool) -> Eq Pipeline
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pipeline -> Pipeline -> Bool
$c/= :: Pipeline -> Pipeline -> Bool
== :: Pipeline -> Pipeline -> Bool
$c== :: Pipeline -> Pipeline -> Bool
Eq, Eq Pipeline
Eq Pipeline =>
(Pipeline -> Pipeline -> Ordering)
-> (Pipeline -> Pipeline -> Bool)
-> (Pipeline -> Pipeline -> Bool)
-> (Pipeline -> Pipeline -> Bool)
-> (Pipeline -> Pipeline -> Bool)
-> (Pipeline -> Pipeline -> Pipeline)
-> (Pipeline -> Pipeline -> Pipeline)
-> Ord Pipeline
Pipeline -> Pipeline -> Bool
Pipeline -> Pipeline -> Ordering
Pipeline -> Pipeline -> Pipeline
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 :: Pipeline -> Pipeline -> Pipeline
$cmin :: Pipeline -> Pipeline -> Pipeline
max :: Pipeline -> Pipeline -> Pipeline
$cmax :: Pipeline -> Pipeline -> Pipeline
>= :: Pipeline -> Pipeline -> Bool
$c>= :: Pipeline -> Pipeline -> Bool
> :: Pipeline -> Pipeline -> Bool
$c> :: Pipeline -> Pipeline -> Bool
<= :: Pipeline -> Pipeline -> Bool
$c<= :: Pipeline -> Pipeline -> Bool
< :: Pipeline -> Pipeline -> Bool
$c< :: Pipeline -> Pipeline -> Bool
compare :: Pipeline -> Pipeline -> Ordering
$ccompare :: Pipeline -> Pipeline -> Ordering
$cp1Ord :: Eq Pipeline
Ord, Ptr b -> Int -> IO Pipeline
Ptr b -> Int -> Pipeline -> IO ()
Ptr Pipeline -> IO Pipeline
Ptr Pipeline -> Int -> IO Pipeline
Ptr Pipeline -> Int -> Pipeline -> IO ()
Ptr Pipeline -> Pipeline -> IO ()
Pipeline -> Int
(Pipeline -> Int)
-> (Pipeline -> Int)
-> (Ptr Pipeline -> Int -> IO Pipeline)
-> (Ptr Pipeline -> Int -> Pipeline -> IO ())
-> (forall b. Ptr b -> Int -> IO Pipeline)
-> (forall b. Ptr b -> Int -> Pipeline -> IO ())
-> (Ptr Pipeline -> IO Pipeline)
-> (Ptr Pipeline -> Pipeline -> IO ())
-> Storable Pipeline
forall b. Ptr b -> Int -> IO Pipeline
forall b. Ptr b -> Int -> Pipeline -> 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 Pipeline -> Pipeline -> IO ()
$cpoke :: Ptr Pipeline -> Pipeline -> IO ()
peek :: Ptr Pipeline -> IO Pipeline
$cpeek :: Ptr Pipeline -> IO Pipeline
pokeByteOff :: Ptr b -> Int -> Pipeline -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Pipeline -> IO ()
peekByteOff :: Ptr b -> Int -> IO Pipeline
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Pipeline
pokeElemOff :: Ptr Pipeline -> Int -> Pipeline -> IO ()
$cpokeElemOff :: Ptr Pipeline -> Int -> Pipeline -> IO ()
peekElemOff :: Ptr Pipeline -> Int -> IO Pipeline
$cpeekElemOff :: Ptr Pipeline -> Int -> IO Pipeline
alignment :: Pipeline -> Int
$calignment :: Pipeline -> Int
sizeOf :: Pipeline -> Int
$csizeOf :: Pipeline -> Int
Storable, Pipeline
Pipeline -> Zero Pipeline
forall a. a -> Zero a
zero :: Pipeline
$czero :: Pipeline
Zero)
  deriving anyclass (Eq Pipeline
Zero Pipeline
(Eq Pipeline, Zero Pipeline) => IsHandle Pipeline
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Pipeline
$cp1IsHandle :: Eq Pipeline
IsHandle)
instance HasObjectType Pipeline where
  objectTypeAndHandle :: Pipeline -> (ObjectType, Word64)
objectTypeAndHandle (Pipeline h :: Word64
h) = (ObjectType
OBJECT_TYPE_PIPELINE, Word64
h)
instance Show Pipeline where
  showsPrec :: Int -> Pipeline -> ShowS
showsPrec p :: Int
p (Pipeline x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Pipeline 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)


-- | VkPipelineLayout - Opaque handle to a pipeline layout object
--
-- = See Also
--
-- 'Vulkan.Core10.Pipeline.ComputePipelineCreateInfo',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_descriptor_update_template.DescriptorUpdateTemplateCreateInfo',
-- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo',
-- 'Vulkan.Extensions.VK_NV_device_generated_commands.IndirectCommandsLayoutTokenNV',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.RayTracingPipelineCreateInfoKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.RayTracingPipelineCreateInfoNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBindDescriptorSets',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdPushConstants',
-- 'Vulkan.Extensions.VK_KHR_push_descriptor.cmdPushDescriptorSetKHR',
-- 'Vulkan.Extensions.VK_KHR_push_descriptor.cmdPushDescriptorSetWithTemplateKHR',
-- 'Vulkan.Core10.PipelineLayout.createPipelineLayout',
-- 'Vulkan.Core10.PipelineLayout.destroyPipelineLayout'
newtype PipelineLayout = PipelineLayout Word64
  deriving newtype (PipelineLayout -> PipelineLayout -> Bool
(PipelineLayout -> PipelineLayout -> Bool)
-> (PipelineLayout -> PipelineLayout -> Bool) -> Eq PipelineLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineLayout -> PipelineLayout -> Bool
$c/= :: PipelineLayout -> PipelineLayout -> Bool
== :: PipelineLayout -> PipelineLayout -> Bool
$c== :: PipelineLayout -> PipelineLayout -> Bool
Eq, Eq PipelineLayout
Eq PipelineLayout =>
(PipelineLayout -> PipelineLayout -> Ordering)
-> (PipelineLayout -> PipelineLayout -> Bool)
-> (PipelineLayout -> PipelineLayout -> Bool)
-> (PipelineLayout -> PipelineLayout -> Bool)
-> (PipelineLayout -> PipelineLayout -> Bool)
-> (PipelineLayout -> PipelineLayout -> PipelineLayout)
-> (PipelineLayout -> PipelineLayout -> PipelineLayout)
-> Ord PipelineLayout
PipelineLayout -> PipelineLayout -> Bool
PipelineLayout -> PipelineLayout -> Ordering
PipelineLayout -> PipelineLayout -> PipelineLayout
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 :: PipelineLayout -> PipelineLayout -> PipelineLayout
$cmin :: PipelineLayout -> PipelineLayout -> PipelineLayout
max :: PipelineLayout -> PipelineLayout -> PipelineLayout
$cmax :: PipelineLayout -> PipelineLayout -> PipelineLayout
>= :: PipelineLayout -> PipelineLayout -> Bool
$c>= :: PipelineLayout -> PipelineLayout -> Bool
> :: PipelineLayout -> PipelineLayout -> Bool
$c> :: PipelineLayout -> PipelineLayout -> Bool
<= :: PipelineLayout -> PipelineLayout -> Bool
$c<= :: PipelineLayout -> PipelineLayout -> Bool
< :: PipelineLayout -> PipelineLayout -> Bool
$c< :: PipelineLayout -> PipelineLayout -> Bool
compare :: PipelineLayout -> PipelineLayout -> Ordering
$ccompare :: PipelineLayout -> PipelineLayout -> Ordering
$cp1Ord :: Eq PipelineLayout
Ord, Ptr b -> Int -> IO PipelineLayout
Ptr b -> Int -> PipelineLayout -> IO ()
Ptr PipelineLayout -> IO PipelineLayout
Ptr PipelineLayout -> Int -> IO PipelineLayout
Ptr PipelineLayout -> Int -> PipelineLayout -> IO ()
Ptr PipelineLayout -> PipelineLayout -> IO ()
PipelineLayout -> Int
(PipelineLayout -> Int)
-> (PipelineLayout -> Int)
-> (Ptr PipelineLayout -> Int -> IO PipelineLayout)
-> (Ptr PipelineLayout -> Int -> PipelineLayout -> IO ())
-> (forall b. Ptr b -> Int -> IO PipelineLayout)
-> (forall b. Ptr b -> Int -> PipelineLayout -> IO ())
-> (Ptr PipelineLayout -> IO PipelineLayout)
-> (Ptr PipelineLayout -> PipelineLayout -> IO ())
-> Storable PipelineLayout
forall b. Ptr b -> Int -> IO PipelineLayout
forall b. Ptr b -> Int -> PipelineLayout -> 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 PipelineLayout -> PipelineLayout -> IO ()
$cpoke :: Ptr PipelineLayout -> PipelineLayout -> IO ()
peek :: Ptr PipelineLayout -> IO PipelineLayout
$cpeek :: Ptr PipelineLayout -> IO PipelineLayout
pokeByteOff :: Ptr b -> Int -> PipelineLayout -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PipelineLayout -> IO ()
peekByteOff :: Ptr b -> Int -> IO PipelineLayout
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PipelineLayout
pokeElemOff :: Ptr PipelineLayout -> Int -> PipelineLayout -> IO ()
$cpokeElemOff :: Ptr PipelineLayout -> Int -> PipelineLayout -> IO ()
peekElemOff :: Ptr PipelineLayout -> Int -> IO PipelineLayout
$cpeekElemOff :: Ptr PipelineLayout -> Int -> IO PipelineLayout
alignment :: PipelineLayout -> Int
$calignment :: PipelineLayout -> Int
sizeOf :: PipelineLayout -> Int
$csizeOf :: PipelineLayout -> Int
Storable, PipelineLayout
PipelineLayout -> Zero PipelineLayout
forall a. a -> Zero a
zero :: PipelineLayout
$czero :: PipelineLayout
Zero)
  deriving anyclass (Eq PipelineLayout
Zero PipelineLayout
(Eq PipelineLayout, Zero PipelineLayout) => IsHandle PipelineLayout
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero PipelineLayout
$cp1IsHandle :: Eq PipelineLayout
IsHandle)
instance HasObjectType PipelineLayout where
  objectTypeAndHandle :: PipelineLayout -> (ObjectType, Word64)
objectTypeAndHandle (PipelineLayout h :: Word64
h) = (ObjectType
OBJECT_TYPE_PIPELINE_LAYOUT, Word64
h)
instance Show PipelineLayout where
  showsPrec :: Int -> PipelineLayout -> ShowS
showsPrec p :: Int
p (PipelineLayout x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PipelineLayout 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)


-- | VkSampler - Opaque handle to a sampler object
--
-- = See Also
--
-- 'Vulkan.Core10.DescriptorSet.DescriptorImageInfo',
-- 'Vulkan.Core10.DescriptorSet.DescriptorSetLayoutBinding',
-- 'Vulkan.Extensions.VK_NVX_image_view_handle.ImageViewHandleInfoNVX',
-- 'Vulkan.Core10.Sampler.createSampler',
-- 'Vulkan.Core10.Sampler.destroySampler'
newtype Sampler = Sampler Word64
  deriving newtype (Sampler -> Sampler -> Bool
(Sampler -> Sampler -> Bool)
-> (Sampler -> Sampler -> Bool) -> Eq Sampler
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Sampler -> Sampler -> Bool
$c/= :: Sampler -> Sampler -> Bool
== :: Sampler -> Sampler -> Bool
$c== :: Sampler -> Sampler -> Bool
Eq, Eq Sampler
Eq Sampler =>
(Sampler -> Sampler -> Ordering)
-> (Sampler -> Sampler -> Bool)
-> (Sampler -> Sampler -> Bool)
-> (Sampler -> Sampler -> Bool)
-> (Sampler -> Sampler -> Bool)
-> (Sampler -> Sampler -> Sampler)
-> (Sampler -> Sampler -> Sampler)
-> Ord Sampler
Sampler -> Sampler -> Bool
Sampler -> Sampler -> Ordering
Sampler -> Sampler -> Sampler
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 :: Sampler -> Sampler -> Sampler
$cmin :: Sampler -> Sampler -> Sampler
max :: Sampler -> Sampler -> Sampler
$cmax :: Sampler -> Sampler -> Sampler
>= :: Sampler -> Sampler -> Bool
$c>= :: Sampler -> Sampler -> Bool
> :: Sampler -> Sampler -> Bool
$c> :: Sampler -> Sampler -> Bool
<= :: Sampler -> Sampler -> Bool
$c<= :: Sampler -> Sampler -> Bool
< :: Sampler -> Sampler -> Bool
$c< :: Sampler -> Sampler -> Bool
compare :: Sampler -> Sampler -> Ordering
$ccompare :: Sampler -> Sampler -> Ordering
$cp1Ord :: Eq Sampler
Ord, Ptr b -> Int -> IO Sampler
Ptr b -> Int -> Sampler -> IO ()
Ptr Sampler -> IO Sampler
Ptr Sampler -> Int -> IO Sampler
Ptr Sampler -> Int -> Sampler -> IO ()
Ptr Sampler -> Sampler -> IO ()
Sampler -> Int
(Sampler -> Int)
-> (Sampler -> Int)
-> (Ptr Sampler -> Int -> IO Sampler)
-> (Ptr Sampler -> Int -> Sampler -> IO ())
-> (forall b. Ptr b -> Int -> IO Sampler)
-> (forall b. Ptr b -> Int -> Sampler -> IO ())
-> (Ptr Sampler -> IO Sampler)
-> (Ptr Sampler -> Sampler -> IO ())
-> Storable Sampler
forall b. Ptr b -> Int -> IO Sampler
forall b. Ptr b -> Int -> Sampler -> 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 Sampler -> Sampler -> IO ()
$cpoke :: Ptr Sampler -> Sampler -> IO ()
peek :: Ptr Sampler -> IO Sampler
$cpeek :: Ptr Sampler -> IO Sampler
pokeByteOff :: Ptr b -> Int -> Sampler -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Sampler -> IO ()
peekByteOff :: Ptr b -> Int -> IO Sampler
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Sampler
pokeElemOff :: Ptr Sampler -> Int -> Sampler -> IO ()
$cpokeElemOff :: Ptr Sampler -> Int -> Sampler -> IO ()
peekElemOff :: Ptr Sampler -> Int -> IO Sampler
$cpeekElemOff :: Ptr Sampler -> Int -> IO Sampler
alignment :: Sampler -> Int
$calignment :: Sampler -> Int
sizeOf :: Sampler -> Int
$csizeOf :: Sampler -> Int
Storable, Sampler
Sampler -> Zero Sampler
forall a. a -> Zero a
zero :: Sampler
$czero :: Sampler
Zero)
  deriving anyclass (Eq Sampler
Zero Sampler
(Eq Sampler, Zero Sampler) => IsHandle Sampler
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Sampler
$cp1IsHandle :: Eq Sampler
IsHandle)
instance HasObjectType Sampler where
  objectTypeAndHandle :: Sampler -> (ObjectType, Word64)
objectTypeAndHandle (Sampler h :: Word64
h) = (ObjectType
OBJECT_TYPE_SAMPLER, Word64
h)
instance Show Sampler where
  showsPrec :: Int -> Sampler -> ShowS
showsPrec p :: Int
p (Sampler x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Sampler 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)


-- | VkDescriptorSet - Opaque handle to a descriptor set object
--
-- = See Also
--
-- 'Vulkan.Core10.DescriptorSet.CopyDescriptorSet',
-- 'Vulkan.Core10.DescriptorSet.WriteDescriptorSet',
-- 'Vulkan.Core10.DescriptorSet.allocateDescriptorSets',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBindDescriptorSets',
-- 'Vulkan.Core10.DescriptorSet.freeDescriptorSets',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_descriptor_update_template.updateDescriptorSetWithTemplate',
-- 'Vulkan.Extensions.VK_KHR_descriptor_update_template.updateDescriptorSetWithTemplateKHR'
newtype DescriptorSet = DescriptorSet Word64
  deriving newtype (DescriptorSet -> DescriptorSet -> Bool
(DescriptorSet -> DescriptorSet -> Bool)
-> (DescriptorSet -> DescriptorSet -> Bool) -> Eq DescriptorSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescriptorSet -> DescriptorSet -> Bool
$c/= :: DescriptorSet -> DescriptorSet -> Bool
== :: DescriptorSet -> DescriptorSet -> Bool
$c== :: DescriptorSet -> DescriptorSet -> Bool
Eq, Eq DescriptorSet
Eq DescriptorSet =>
(DescriptorSet -> DescriptorSet -> Ordering)
-> (DescriptorSet -> DescriptorSet -> Bool)
-> (DescriptorSet -> DescriptorSet -> Bool)
-> (DescriptorSet -> DescriptorSet -> Bool)
-> (DescriptorSet -> DescriptorSet -> Bool)
-> (DescriptorSet -> DescriptorSet -> DescriptorSet)
-> (DescriptorSet -> DescriptorSet -> DescriptorSet)
-> Ord DescriptorSet
DescriptorSet -> DescriptorSet -> Bool
DescriptorSet -> DescriptorSet -> Ordering
DescriptorSet -> DescriptorSet -> DescriptorSet
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 :: DescriptorSet -> DescriptorSet -> DescriptorSet
$cmin :: DescriptorSet -> DescriptorSet -> DescriptorSet
max :: DescriptorSet -> DescriptorSet -> DescriptorSet
$cmax :: DescriptorSet -> DescriptorSet -> DescriptorSet
>= :: DescriptorSet -> DescriptorSet -> Bool
$c>= :: DescriptorSet -> DescriptorSet -> Bool
> :: DescriptorSet -> DescriptorSet -> Bool
$c> :: DescriptorSet -> DescriptorSet -> Bool
<= :: DescriptorSet -> DescriptorSet -> Bool
$c<= :: DescriptorSet -> DescriptorSet -> Bool
< :: DescriptorSet -> DescriptorSet -> Bool
$c< :: DescriptorSet -> DescriptorSet -> Bool
compare :: DescriptorSet -> DescriptorSet -> Ordering
$ccompare :: DescriptorSet -> DescriptorSet -> Ordering
$cp1Ord :: Eq DescriptorSet
Ord, Ptr b -> Int -> IO DescriptorSet
Ptr b -> Int -> DescriptorSet -> IO ()
Ptr DescriptorSet -> IO DescriptorSet
Ptr DescriptorSet -> Int -> IO DescriptorSet
Ptr DescriptorSet -> Int -> DescriptorSet -> IO ()
Ptr DescriptorSet -> DescriptorSet -> IO ()
DescriptorSet -> Int
(DescriptorSet -> Int)
-> (DescriptorSet -> Int)
-> (Ptr DescriptorSet -> Int -> IO DescriptorSet)
-> (Ptr DescriptorSet -> Int -> DescriptorSet -> IO ())
-> (forall b. Ptr b -> Int -> IO DescriptorSet)
-> (forall b. Ptr b -> Int -> DescriptorSet -> IO ())
-> (Ptr DescriptorSet -> IO DescriptorSet)
-> (Ptr DescriptorSet -> DescriptorSet -> IO ())
-> Storable DescriptorSet
forall b. Ptr b -> Int -> IO DescriptorSet
forall b. Ptr b -> Int -> DescriptorSet -> 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 DescriptorSet -> DescriptorSet -> IO ()
$cpoke :: Ptr DescriptorSet -> DescriptorSet -> IO ()
peek :: Ptr DescriptorSet -> IO DescriptorSet
$cpeek :: Ptr DescriptorSet -> IO DescriptorSet
pokeByteOff :: Ptr b -> Int -> DescriptorSet -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DescriptorSet -> IO ()
peekByteOff :: Ptr b -> Int -> IO DescriptorSet
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DescriptorSet
pokeElemOff :: Ptr DescriptorSet -> Int -> DescriptorSet -> IO ()
$cpokeElemOff :: Ptr DescriptorSet -> Int -> DescriptorSet -> IO ()
peekElemOff :: Ptr DescriptorSet -> Int -> IO DescriptorSet
$cpeekElemOff :: Ptr DescriptorSet -> Int -> IO DescriptorSet
alignment :: DescriptorSet -> Int
$calignment :: DescriptorSet -> Int
sizeOf :: DescriptorSet -> Int
$csizeOf :: DescriptorSet -> Int
Storable, DescriptorSet
DescriptorSet -> Zero DescriptorSet
forall a. a -> Zero a
zero :: DescriptorSet
$czero :: DescriptorSet
Zero)
  deriving anyclass (Eq DescriptorSet
Zero DescriptorSet
(Eq DescriptorSet, Zero DescriptorSet) => IsHandle DescriptorSet
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DescriptorSet
$cp1IsHandle :: Eq DescriptorSet
IsHandle)
instance HasObjectType DescriptorSet where
  objectTypeAndHandle :: DescriptorSet -> (ObjectType, Word64)
objectTypeAndHandle (DescriptorSet h :: Word64
h) = (ObjectType
OBJECT_TYPE_DESCRIPTOR_SET, Word64
h)
instance Show DescriptorSet where
  showsPrec :: Int -> DescriptorSet -> ShowS
showsPrec p :: Int
p (DescriptorSet x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DescriptorSet 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)


-- | VkDescriptorSetLayout - Opaque handle to a descriptor set layout object
--
-- = See Also
--
-- 'Vulkan.Core10.DescriptorSet.DescriptorSetAllocateInfo',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_descriptor_update_template.DescriptorUpdateTemplateCreateInfo',
-- 'Vulkan.Core10.PipelineLayout.PipelineLayoutCreateInfo',
-- 'Vulkan.Core10.DescriptorSet.createDescriptorSetLayout',
-- 'Vulkan.Core10.DescriptorSet.destroyDescriptorSetLayout'
newtype DescriptorSetLayout = DescriptorSetLayout Word64
  deriving newtype (DescriptorSetLayout -> DescriptorSetLayout -> Bool
(DescriptorSetLayout -> DescriptorSetLayout -> Bool)
-> (DescriptorSetLayout -> DescriptorSetLayout -> Bool)
-> Eq DescriptorSetLayout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
$c/= :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
== :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
$c== :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
Eq, Eq DescriptorSetLayout
Eq DescriptorSetLayout =>
(DescriptorSetLayout -> DescriptorSetLayout -> Ordering)
-> (DescriptorSetLayout -> DescriptorSetLayout -> Bool)
-> (DescriptorSetLayout -> DescriptorSetLayout -> Bool)
-> (DescriptorSetLayout -> DescriptorSetLayout -> Bool)
-> (DescriptorSetLayout -> DescriptorSetLayout -> Bool)
-> (DescriptorSetLayout
    -> DescriptorSetLayout -> DescriptorSetLayout)
-> (DescriptorSetLayout
    -> DescriptorSetLayout -> DescriptorSetLayout)
-> Ord DescriptorSetLayout
DescriptorSetLayout -> DescriptorSetLayout -> Bool
DescriptorSetLayout -> DescriptorSetLayout -> Ordering
DescriptorSetLayout -> DescriptorSetLayout -> DescriptorSetLayout
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 :: DescriptorSetLayout -> DescriptorSetLayout -> DescriptorSetLayout
$cmin :: DescriptorSetLayout -> DescriptorSetLayout -> DescriptorSetLayout
max :: DescriptorSetLayout -> DescriptorSetLayout -> DescriptorSetLayout
$cmax :: DescriptorSetLayout -> DescriptorSetLayout -> DescriptorSetLayout
>= :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
$c>= :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
> :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
$c> :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
<= :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
$c<= :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
< :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
$c< :: DescriptorSetLayout -> DescriptorSetLayout -> Bool
compare :: DescriptorSetLayout -> DescriptorSetLayout -> Ordering
$ccompare :: DescriptorSetLayout -> DescriptorSetLayout -> Ordering
$cp1Ord :: Eq DescriptorSetLayout
Ord, Ptr b -> Int -> IO DescriptorSetLayout
Ptr b -> Int -> DescriptorSetLayout -> IO ()
Ptr DescriptorSetLayout -> IO DescriptorSetLayout
Ptr DescriptorSetLayout -> Int -> IO DescriptorSetLayout
Ptr DescriptorSetLayout -> Int -> DescriptorSetLayout -> IO ()
Ptr DescriptorSetLayout -> DescriptorSetLayout -> IO ()
DescriptorSetLayout -> Int
(DescriptorSetLayout -> Int)
-> (DescriptorSetLayout -> Int)
-> (Ptr DescriptorSetLayout -> Int -> IO DescriptorSetLayout)
-> (Ptr DescriptorSetLayout -> Int -> DescriptorSetLayout -> IO ())
-> (forall b. Ptr b -> Int -> IO DescriptorSetLayout)
-> (forall b. Ptr b -> Int -> DescriptorSetLayout -> IO ())
-> (Ptr DescriptorSetLayout -> IO DescriptorSetLayout)
-> (Ptr DescriptorSetLayout -> DescriptorSetLayout -> IO ())
-> Storable DescriptorSetLayout
forall b. Ptr b -> Int -> IO DescriptorSetLayout
forall b. Ptr b -> Int -> DescriptorSetLayout -> 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 DescriptorSetLayout -> DescriptorSetLayout -> IO ()
$cpoke :: Ptr DescriptorSetLayout -> DescriptorSetLayout -> IO ()
peek :: Ptr DescriptorSetLayout -> IO DescriptorSetLayout
$cpeek :: Ptr DescriptorSetLayout -> IO DescriptorSetLayout
pokeByteOff :: Ptr b -> Int -> DescriptorSetLayout -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DescriptorSetLayout -> IO ()
peekByteOff :: Ptr b -> Int -> IO DescriptorSetLayout
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DescriptorSetLayout
pokeElemOff :: Ptr DescriptorSetLayout -> Int -> DescriptorSetLayout -> IO ()
$cpokeElemOff :: Ptr DescriptorSetLayout -> Int -> DescriptorSetLayout -> IO ()
peekElemOff :: Ptr DescriptorSetLayout -> Int -> IO DescriptorSetLayout
$cpeekElemOff :: Ptr DescriptorSetLayout -> Int -> IO DescriptorSetLayout
alignment :: DescriptorSetLayout -> Int
$calignment :: DescriptorSetLayout -> Int
sizeOf :: DescriptorSetLayout -> Int
$csizeOf :: DescriptorSetLayout -> Int
Storable, DescriptorSetLayout
DescriptorSetLayout -> Zero DescriptorSetLayout
forall a. a -> Zero a
zero :: DescriptorSetLayout
$czero :: DescriptorSetLayout
Zero)
  deriving anyclass (Eq DescriptorSetLayout
Zero DescriptorSetLayout
(Eq DescriptorSetLayout, Zero DescriptorSetLayout) =>
IsHandle DescriptorSetLayout
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DescriptorSetLayout
$cp1IsHandle :: Eq DescriptorSetLayout
IsHandle)
instance HasObjectType DescriptorSetLayout where
  objectTypeAndHandle :: DescriptorSetLayout -> (ObjectType, Word64)
objectTypeAndHandle (DescriptorSetLayout h :: Word64
h) = (ObjectType
OBJECT_TYPE_DESCRIPTOR_SET_LAYOUT, Word64
h)
instance Show DescriptorSetLayout where
  showsPrec :: Int -> DescriptorSetLayout -> ShowS
showsPrec p :: Int
p (DescriptorSetLayout x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DescriptorSetLayout 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)


-- | VkDescriptorPool - Opaque handle to a descriptor pool object
--
-- = See Also
--
-- 'Vulkan.Core10.DescriptorSet.DescriptorSetAllocateInfo',
-- 'Vulkan.Core10.DescriptorSet.createDescriptorPool',
-- 'Vulkan.Core10.DescriptorSet.destroyDescriptorPool',
-- 'Vulkan.Core10.DescriptorSet.freeDescriptorSets',
-- 'Vulkan.Core10.DescriptorSet.resetDescriptorPool'
newtype DescriptorPool = DescriptorPool Word64
  deriving newtype (DescriptorPool -> DescriptorPool -> Bool
(DescriptorPool -> DescriptorPool -> Bool)
-> (DescriptorPool -> DescriptorPool -> Bool) -> Eq DescriptorPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescriptorPool -> DescriptorPool -> Bool
$c/= :: DescriptorPool -> DescriptorPool -> Bool
== :: DescriptorPool -> DescriptorPool -> Bool
$c== :: DescriptorPool -> DescriptorPool -> Bool
Eq, Eq DescriptorPool
Eq DescriptorPool =>
(DescriptorPool -> DescriptorPool -> Ordering)
-> (DescriptorPool -> DescriptorPool -> Bool)
-> (DescriptorPool -> DescriptorPool -> Bool)
-> (DescriptorPool -> DescriptorPool -> Bool)
-> (DescriptorPool -> DescriptorPool -> Bool)
-> (DescriptorPool -> DescriptorPool -> DescriptorPool)
-> (DescriptorPool -> DescriptorPool -> DescriptorPool)
-> Ord DescriptorPool
DescriptorPool -> DescriptorPool -> Bool
DescriptorPool -> DescriptorPool -> Ordering
DescriptorPool -> DescriptorPool -> DescriptorPool
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 :: DescriptorPool -> DescriptorPool -> DescriptorPool
$cmin :: DescriptorPool -> DescriptorPool -> DescriptorPool
max :: DescriptorPool -> DescriptorPool -> DescriptorPool
$cmax :: DescriptorPool -> DescriptorPool -> DescriptorPool
>= :: DescriptorPool -> DescriptorPool -> Bool
$c>= :: DescriptorPool -> DescriptorPool -> Bool
> :: DescriptorPool -> DescriptorPool -> Bool
$c> :: DescriptorPool -> DescriptorPool -> Bool
<= :: DescriptorPool -> DescriptorPool -> Bool
$c<= :: DescriptorPool -> DescriptorPool -> Bool
< :: DescriptorPool -> DescriptorPool -> Bool
$c< :: DescriptorPool -> DescriptorPool -> Bool
compare :: DescriptorPool -> DescriptorPool -> Ordering
$ccompare :: DescriptorPool -> DescriptorPool -> Ordering
$cp1Ord :: Eq DescriptorPool
Ord, Ptr b -> Int -> IO DescriptorPool
Ptr b -> Int -> DescriptorPool -> IO ()
Ptr DescriptorPool -> IO DescriptorPool
Ptr DescriptorPool -> Int -> IO DescriptorPool
Ptr DescriptorPool -> Int -> DescriptorPool -> IO ()
Ptr DescriptorPool -> DescriptorPool -> IO ()
DescriptorPool -> Int
(DescriptorPool -> Int)
-> (DescriptorPool -> Int)
-> (Ptr DescriptorPool -> Int -> IO DescriptorPool)
-> (Ptr DescriptorPool -> Int -> DescriptorPool -> IO ())
-> (forall b. Ptr b -> Int -> IO DescriptorPool)
-> (forall b. Ptr b -> Int -> DescriptorPool -> IO ())
-> (Ptr DescriptorPool -> IO DescriptorPool)
-> (Ptr DescriptorPool -> DescriptorPool -> IO ())
-> Storable DescriptorPool
forall b. Ptr b -> Int -> IO DescriptorPool
forall b. Ptr b -> Int -> DescriptorPool -> 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 DescriptorPool -> DescriptorPool -> IO ()
$cpoke :: Ptr DescriptorPool -> DescriptorPool -> IO ()
peek :: Ptr DescriptorPool -> IO DescriptorPool
$cpeek :: Ptr DescriptorPool -> IO DescriptorPool
pokeByteOff :: Ptr b -> Int -> DescriptorPool -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DescriptorPool -> IO ()
peekByteOff :: Ptr b -> Int -> IO DescriptorPool
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DescriptorPool
pokeElemOff :: Ptr DescriptorPool -> Int -> DescriptorPool -> IO ()
$cpokeElemOff :: Ptr DescriptorPool -> Int -> DescriptorPool -> IO ()
peekElemOff :: Ptr DescriptorPool -> Int -> IO DescriptorPool
$cpeekElemOff :: Ptr DescriptorPool -> Int -> IO DescriptorPool
alignment :: DescriptorPool -> Int
$calignment :: DescriptorPool -> Int
sizeOf :: DescriptorPool -> Int
$csizeOf :: DescriptorPool -> Int
Storable, DescriptorPool
DescriptorPool -> Zero DescriptorPool
forall a. a -> Zero a
zero :: DescriptorPool
$czero :: DescriptorPool
Zero)
  deriving anyclass (Eq DescriptorPool
Zero DescriptorPool
(Eq DescriptorPool, Zero DescriptorPool) => IsHandle DescriptorPool
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DescriptorPool
$cp1IsHandle :: Eq DescriptorPool
IsHandle)
instance HasObjectType DescriptorPool where
  objectTypeAndHandle :: DescriptorPool -> (ObjectType, Word64)
objectTypeAndHandle (DescriptorPool h :: Word64
h) = (ObjectType
OBJECT_TYPE_DESCRIPTOR_POOL, Word64
h)
instance Show DescriptorPool where
  showsPrec :: Int -> DescriptorPool -> ShowS
showsPrec p :: Int
p (DescriptorPool x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DescriptorPool 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)


-- | VkFence - Opaque handle to a fence object
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_swapchain.AcquireNextImageInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_fence_fd.FenceGetFdInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_fence_win32.FenceGetWin32HandleInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_fence_fd.ImportFenceFdInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_fence_win32.ImportFenceWin32HandleInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.acquireNextImageKHR',
-- 'Vulkan.Core10.Fence.createFence', 'Vulkan.Core10.Fence.destroyFence',
-- 'Vulkan.Core10.Fence.getFenceStatus',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.queueBindSparse',
-- 'Vulkan.Core10.Queue.queueSubmit',
-- 'Vulkan.Extensions.VK_EXT_display_control.registerDeviceEventEXT',
-- 'Vulkan.Extensions.VK_EXT_display_control.registerDisplayEventEXT',
-- 'Vulkan.Core10.Fence.resetFences', 'Vulkan.Core10.Fence.waitForFences'
newtype Fence = Fence Word64
  deriving newtype (Fence -> Fence -> Bool
(Fence -> Fence -> Bool) -> (Fence -> Fence -> Bool) -> Eq Fence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Fence -> Fence -> Bool
$c/= :: Fence -> Fence -> Bool
== :: Fence -> Fence -> Bool
$c== :: Fence -> Fence -> Bool
Eq, Eq Fence
Eq Fence =>
(Fence -> Fence -> Ordering)
-> (Fence -> Fence -> Bool)
-> (Fence -> Fence -> Bool)
-> (Fence -> Fence -> Bool)
-> (Fence -> Fence -> Bool)
-> (Fence -> Fence -> Fence)
-> (Fence -> Fence -> Fence)
-> Ord Fence
Fence -> Fence -> Bool
Fence -> Fence -> Ordering
Fence -> Fence -> Fence
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 :: Fence -> Fence -> Fence
$cmin :: Fence -> Fence -> Fence
max :: Fence -> Fence -> Fence
$cmax :: Fence -> Fence -> Fence
>= :: Fence -> Fence -> Bool
$c>= :: Fence -> Fence -> Bool
> :: Fence -> Fence -> Bool
$c> :: Fence -> Fence -> Bool
<= :: Fence -> Fence -> Bool
$c<= :: Fence -> Fence -> Bool
< :: Fence -> Fence -> Bool
$c< :: Fence -> Fence -> Bool
compare :: Fence -> Fence -> Ordering
$ccompare :: Fence -> Fence -> Ordering
$cp1Ord :: Eq Fence
Ord, Ptr b -> Int -> IO Fence
Ptr b -> Int -> Fence -> IO ()
Ptr Fence -> IO Fence
Ptr Fence -> Int -> IO Fence
Ptr Fence -> Int -> Fence -> IO ()
Ptr Fence -> Fence -> IO ()
Fence -> Int
(Fence -> Int)
-> (Fence -> Int)
-> (Ptr Fence -> Int -> IO Fence)
-> (Ptr Fence -> Int -> Fence -> IO ())
-> (forall b. Ptr b -> Int -> IO Fence)
-> (forall b. Ptr b -> Int -> Fence -> IO ())
-> (Ptr Fence -> IO Fence)
-> (Ptr Fence -> Fence -> IO ())
-> Storable Fence
forall b. Ptr b -> Int -> IO Fence
forall b. Ptr b -> Int -> Fence -> 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 Fence -> Fence -> IO ()
$cpoke :: Ptr Fence -> Fence -> IO ()
peek :: Ptr Fence -> IO Fence
$cpeek :: Ptr Fence -> IO Fence
pokeByteOff :: Ptr b -> Int -> Fence -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Fence -> IO ()
peekByteOff :: Ptr b -> Int -> IO Fence
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Fence
pokeElemOff :: Ptr Fence -> Int -> Fence -> IO ()
$cpokeElemOff :: Ptr Fence -> Int -> Fence -> IO ()
peekElemOff :: Ptr Fence -> Int -> IO Fence
$cpeekElemOff :: Ptr Fence -> Int -> IO Fence
alignment :: Fence -> Int
$calignment :: Fence -> Int
sizeOf :: Fence -> Int
$csizeOf :: Fence -> Int
Storable, Fence
Fence -> Zero Fence
forall a. a -> Zero a
zero :: Fence
$czero :: Fence
Zero)
  deriving anyclass (Eq Fence
Zero Fence
(Eq Fence, Zero Fence) => IsHandle Fence
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Fence
$cp1IsHandle :: Eq Fence
IsHandle)
instance HasObjectType Fence where
  objectTypeAndHandle :: Fence -> (ObjectType, Word64)
objectTypeAndHandle (Fence h :: Word64
h) = (ObjectType
OBJECT_TYPE_FENCE, Word64
h)
instance Show Fence where
  showsPrec :: Int -> Fence -> ShowS
showsPrec p :: Int
p (Fence x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Fence 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)


-- | VkSemaphore - Opaque handle to a semaphore object
--
-- = See Also
--
-- 'Vulkan.Extensions.VK_KHR_swapchain.AcquireNextImageInfoKHR',
-- 'Vulkan.Core10.SparseResourceMemoryManagement.BindSparseInfo',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_fd.ImportSemaphoreFdInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_win32.ImportSemaphoreWin32HandleInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_swapchain.PresentInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_fd.SemaphoreGetFdInfoKHR',
-- 'Vulkan.Extensions.VK_KHR_external_semaphore_win32.SemaphoreGetWin32HandleInfoKHR',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.SemaphoreSignalInfo',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.SemaphoreWaitInfo',
-- 'Vulkan.Core10.Queue.SubmitInfo',
-- 'Vulkan.Extensions.VK_KHR_swapchain.acquireNextImageKHR',
-- 'Vulkan.Core10.QueueSemaphore.createSemaphore',
-- 'Vulkan.Core10.QueueSemaphore.destroySemaphore',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.getSemaphoreCounterValue',
-- 'Vulkan.Extensions.VK_KHR_timeline_semaphore.getSemaphoreCounterValueKHR'
newtype Semaphore = Semaphore Word64
  deriving newtype (Semaphore -> Semaphore -> Bool
(Semaphore -> Semaphore -> Bool)
-> (Semaphore -> Semaphore -> Bool) -> Eq Semaphore
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Semaphore -> Semaphore -> Bool
$c/= :: Semaphore -> Semaphore -> Bool
== :: Semaphore -> Semaphore -> Bool
$c== :: Semaphore -> Semaphore -> Bool
Eq, Eq Semaphore
Eq Semaphore =>
(Semaphore -> Semaphore -> Ordering)
-> (Semaphore -> Semaphore -> Bool)
-> (Semaphore -> Semaphore -> Bool)
-> (Semaphore -> Semaphore -> Bool)
-> (Semaphore -> Semaphore -> Bool)
-> (Semaphore -> Semaphore -> Semaphore)
-> (Semaphore -> Semaphore -> Semaphore)
-> Ord Semaphore
Semaphore -> Semaphore -> Bool
Semaphore -> Semaphore -> Ordering
Semaphore -> Semaphore -> Semaphore
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 :: Semaphore -> Semaphore -> Semaphore
$cmin :: Semaphore -> Semaphore -> Semaphore
max :: Semaphore -> Semaphore -> Semaphore
$cmax :: Semaphore -> Semaphore -> Semaphore
>= :: Semaphore -> Semaphore -> Bool
$c>= :: Semaphore -> Semaphore -> Bool
> :: Semaphore -> Semaphore -> Bool
$c> :: Semaphore -> Semaphore -> Bool
<= :: Semaphore -> Semaphore -> Bool
$c<= :: Semaphore -> Semaphore -> Bool
< :: Semaphore -> Semaphore -> Bool
$c< :: Semaphore -> Semaphore -> Bool
compare :: Semaphore -> Semaphore -> Ordering
$ccompare :: Semaphore -> Semaphore -> Ordering
$cp1Ord :: Eq Semaphore
Ord, Ptr b -> Int -> IO Semaphore
Ptr b -> Int -> Semaphore -> IO ()
Ptr Semaphore -> IO Semaphore
Ptr Semaphore -> Int -> IO Semaphore
Ptr Semaphore -> Int -> Semaphore -> IO ()
Ptr Semaphore -> Semaphore -> IO ()
Semaphore -> Int
(Semaphore -> Int)
-> (Semaphore -> Int)
-> (Ptr Semaphore -> Int -> IO Semaphore)
-> (Ptr Semaphore -> Int -> Semaphore -> IO ())
-> (forall b. Ptr b -> Int -> IO Semaphore)
-> (forall b. Ptr b -> Int -> Semaphore -> IO ())
-> (Ptr Semaphore -> IO Semaphore)
-> (Ptr Semaphore -> Semaphore -> IO ())
-> Storable Semaphore
forall b. Ptr b -> Int -> IO Semaphore
forall b. Ptr b -> Int -> Semaphore -> 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 Semaphore -> Semaphore -> IO ()
$cpoke :: Ptr Semaphore -> Semaphore -> IO ()
peek :: Ptr Semaphore -> IO Semaphore
$cpeek :: Ptr Semaphore -> IO Semaphore
pokeByteOff :: Ptr b -> Int -> Semaphore -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Semaphore -> IO ()
peekByteOff :: Ptr b -> Int -> IO Semaphore
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Semaphore
pokeElemOff :: Ptr Semaphore -> Int -> Semaphore -> IO ()
$cpokeElemOff :: Ptr Semaphore -> Int -> Semaphore -> IO ()
peekElemOff :: Ptr Semaphore -> Int -> IO Semaphore
$cpeekElemOff :: Ptr Semaphore -> Int -> IO Semaphore
alignment :: Semaphore -> Int
$calignment :: Semaphore -> Int
sizeOf :: Semaphore -> Int
$csizeOf :: Semaphore -> Int
Storable, Semaphore
Semaphore -> Zero Semaphore
forall a. a -> Zero a
zero :: Semaphore
$czero :: Semaphore
Zero)
  deriving anyclass (Eq Semaphore
Zero Semaphore
(Eq Semaphore, Zero Semaphore) => IsHandle Semaphore
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Semaphore
$cp1IsHandle :: Eq Semaphore
IsHandle)
instance HasObjectType Semaphore where
  objectTypeAndHandle :: Semaphore -> (ObjectType, Word64)
objectTypeAndHandle (Semaphore h :: Word64
h) = (ObjectType
OBJECT_TYPE_SEMAPHORE, Word64
h)
instance Show Semaphore where
  showsPrec :: Int -> Semaphore -> ShowS
showsPrec p :: Int
p (Semaphore x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Semaphore 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)


-- | VkEvent - Opaque handle to an event object
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBufferBuilding.cmdResetEvent',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdSetEvent',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdWaitEvents',
-- 'Vulkan.Core10.Event.createEvent', 'Vulkan.Core10.Event.destroyEvent',
-- 'Vulkan.Core10.Event.getEventStatus', 'Vulkan.Core10.Event.resetEvent',
-- 'Vulkan.Core10.Event.setEvent'
newtype Event = Event Word64
  deriving newtype (Event -> Event -> Bool
(Event -> Event -> Bool) -> (Event -> Event -> Bool) -> Eq Event
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c== :: Event -> Event -> Bool
Eq, Eq Event
Eq Event =>
(Event -> Event -> Ordering)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Event)
-> (Event -> Event -> Event)
-> Ord Event
Event -> Event -> Bool
Event -> Event -> Ordering
Event -> Event -> Event
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 :: Event -> Event -> Event
$cmin :: Event -> Event -> Event
max :: Event -> Event -> Event
$cmax :: Event -> Event -> Event
>= :: Event -> Event -> Bool
$c>= :: Event -> Event -> Bool
> :: Event -> Event -> Bool
$c> :: Event -> Event -> Bool
<= :: Event -> Event -> Bool
$c<= :: Event -> Event -> Bool
< :: Event -> Event -> Bool
$c< :: Event -> Event -> Bool
compare :: Event -> Event -> Ordering
$ccompare :: Event -> Event -> Ordering
$cp1Ord :: Eq Event
Ord, Ptr b -> Int -> IO Event
Ptr b -> Int -> Event -> IO ()
Ptr Event -> IO Event
Ptr Event -> Int -> IO Event
Ptr Event -> Int -> Event -> IO ()
Ptr Event -> Event -> IO ()
Event -> Int
(Event -> Int)
-> (Event -> Int)
-> (Ptr Event -> Int -> IO Event)
-> (Ptr Event -> Int -> Event -> IO ())
-> (forall b. Ptr b -> Int -> IO Event)
-> (forall b. Ptr b -> Int -> Event -> IO ())
-> (Ptr Event -> IO Event)
-> (Ptr Event -> Event -> IO ())
-> Storable Event
forall b. Ptr b -> Int -> IO Event
forall b. Ptr b -> Int -> Event -> 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 Event -> Event -> IO ()
$cpoke :: Ptr Event -> Event -> IO ()
peek :: Ptr Event -> IO Event
$cpeek :: Ptr Event -> IO Event
pokeByteOff :: Ptr b -> Int -> Event -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Event -> IO ()
peekByteOff :: Ptr b -> Int -> IO Event
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Event
pokeElemOff :: Ptr Event -> Int -> Event -> IO ()
$cpokeElemOff :: Ptr Event -> Int -> Event -> IO ()
peekElemOff :: Ptr Event -> Int -> IO Event
$cpeekElemOff :: Ptr Event -> Int -> IO Event
alignment :: Event -> Int
$calignment :: Event -> Int
sizeOf :: Event -> Int
$csizeOf :: Event -> Int
Storable, Event
Event -> Zero Event
forall a. a -> Zero a
zero :: Event
$czero :: Event
Zero)
  deriving anyclass (Eq Event
Zero Event
(Eq Event, Zero Event) => IsHandle Event
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Event
$cp1IsHandle :: Eq Event
IsHandle)
instance HasObjectType Event where
  objectTypeAndHandle :: Event -> (ObjectType, Word64)
objectTypeAndHandle (Event h :: Word64
h) = (ObjectType
OBJECT_TYPE_EVENT, Word64
h)
instance Show Event where
  showsPrec :: Int -> Event -> ShowS
showsPrec p :: Int
p (Event x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Event 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)


-- | VkQueryPool - Opaque handle to a query pool object
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBufferBuilding.cmdBeginQuery',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdBeginQueryIndexedEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdCopyQueryPoolResults',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdEndQuery',
-- 'Vulkan.Extensions.VK_EXT_transform_feedback.cmdEndQueryIndexedEXT',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdResetQueryPool',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.cmdWriteAccelerationStructuresPropertiesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdWriteAccelerationStructuresPropertiesNV',
-- 'Vulkan.Core10.CommandBufferBuilding.cmdWriteTimestamp',
-- 'Vulkan.Core10.Query.createQueryPool',
-- 'Vulkan.Core10.Query.destroyQueryPool',
-- 'Vulkan.Core10.Query.getQueryPoolResults',
-- 'Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset.resetQueryPool',
-- 'Vulkan.Extensions.VK_EXT_host_query_reset.resetQueryPoolEXT'
newtype QueryPool = QueryPool Word64
  deriving newtype (QueryPool -> QueryPool -> Bool
(QueryPool -> QueryPool -> Bool)
-> (QueryPool -> QueryPool -> Bool) -> Eq QueryPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryPool -> QueryPool -> Bool
$c/= :: QueryPool -> QueryPool -> Bool
== :: QueryPool -> QueryPool -> Bool
$c== :: QueryPool -> QueryPool -> Bool
Eq, Eq QueryPool
Eq QueryPool =>
(QueryPool -> QueryPool -> Ordering)
-> (QueryPool -> QueryPool -> Bool)
-> (QueryPool -> QueryPool -> Bool)
-> (QueryPool -> QueryPool -> Bool)
-> (QueryPool -> QueryPool -> Bool)
-> (QueryPool -> QueryPool -> QueryPool)
-> (QueryPool -> QueryPool -> QueryPool)
-> Ord QueryPool
QueryPool -> QueryPool -> Bool
QueryPool -> QueryPool -> Ordering
QueryPool -> QueryPool -> QueryPool
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 :: QueryPool -> QueryPool -> QueryPool
$cmin :: QueryPool -> QueryPool -> QueryPool
max :: QueryPool -> QueryPool -> QueryPool
$cmax :: QueryPool -> QueryPool -> QueryPool
>= :: QueryPool -> QueryPool -> Bool
$c>= :: QueryPool -> QueryPool -> Bool
> :: QueryPool -> QueryPool -> Bool
$c> :: QueryPool -> QueryPool -> Bool
<= :: QueryPool -> QueryPool -> Bool
$c<= :: QueryPool -> QueryPool -> Bool
< :: QueryPool -> QueryPool -> Bool
$c< :: QueryPool -> QueryPool -> Bool
compare :: QueryPool -> QueryPool -> Ordering
$ccompare :: QueryPool -> QueryPool -> Ordering
$cp1Ord :: Eq QueryPool
Ord, Ptr b -> Int -> IO QueryPool
Ptr b -> Int -> QueryPool -> IO ()
Ptr QueryPool -> IO QueryPool
Ptr QueryPool -> Int -> IO QueryPool
Ptr QueryPool -> Int -> QueryPool -> IO ()
Ptr QueryPool -> QueryPool -> IO ()
QueryPool -> Int
(QueryPool -> Int)
-> (QueryPool -> Int)
-> (Ptr QueryPool -> Int -> IO QueryPool)
-> (Ptr QueryPool -> Int -> QueryPool -> IO ())
-> (forall b. Ptr b -> Int -> IO QueryPool)
-> (forall b. Ptr b -> Int -> QueryPool -> IO ())
-> (Ptr QueryPool -> IO QueryPool)
-> (Ptr QueryPool -> QueryPool -> IO ())
-> Storable QueryPool
forall b. Ptr b -> Int -> IO QueryPool
forall b. Ptr b -> Int -> QueryPool -> 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 QueryPool -> QueryPool -> IO ()
$cpoke :: Ptr QueryPool -> QueryPool -> IO ()
peek :: Ptr QueryPool -> IO QueryPool
$cpeek :: Ptr QueryPool -> IO QueryPool
pokeByteOff :: Ptr b -> Int -> QueryPool -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> QueryPool -> IO ()
peekByteOff :: Ptr b -> Int -> IO QueryPool
$cpeekByteOff :: forall b. Ptr b -> Int -> IO QueryPool
pokeElemOff :: Ptr QueryPool -> Int -> QueryPool -> IO ()
$cpokeElemOff :: Ptr QueryPool -> Int -> QueryPool -> IO ()
peekElemOff :: Ptr QueryPool -> Int -> IO QueryPool
$cpeekElemOff :: Ptr QueryPool -> Int -> IO QueryPool
alignment :: QueryPool -> Int
$calignment :: QueryPool -> Int
sizeOf :: QueryPool -> Int
$csizeOf :: QueryPool -> Int
Storable, QueryPool
QueryPool -> Zero QueryPool
forall a. a -> Zero a
zero :: QueryPool
$czero :: QueryPool
Zero)
  deriving anyclass (Eq QueryPool
Zero QueryPool
(Eq QueryPool, Zero QueryPool) => IsHandle QueryPool
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero QueryPool
$cp1IsHandle :: Eq QueryPool
IsHandle)
instance HasObjectType QueryPool where
  objectTypeAndHandle :: QueryPool -> (ObjectType, Word64)
objectTypeAndHandle (QueryPool h :: Word64
h) = (ObjectType
OBJECT_TYPE_QUERY_POOL, Word64
h)
instance Show QueryPool where
  showsPrec :: Int -> QueryPool -> ShowS
showsPrec p :: Int
p (QueryPool x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "QueryPool 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)


-- | VkFramebuffer - Opaque handle to a framebuffer object
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo',
-- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo',
-- 'Vulkan.Core10.Pass.createFramebuffer',
-- 'Vulkan.Core10.Pass.destroyFramebuffer'
newtype Framebuffer = Framebuffer Word64
  deriving newtype (Framebuffer -> Framebuffer -> Bool
(Framebuffer -> Framebuffer -> Bool)
-> (Framebuffer -> Framebuffer -> Bool) -> Eq Framebuffer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Framebuffer -> Framebuffer -> Bool
$c/= :: Framebuffer -> Framebuffer -> Bool
== :: Framebuffer -> Framebuffer -> Bool
$c== :: Framebuffer -> Framebuffer -> Bool
Eq, Eq Framebuffer
Eq Framebuffer =>
(Framebuffer -> Framebuffer -> Ordering)
-> (Framebuffer -> Framebuffer -> Bool)
-> (Framebuffer -> Framebuffer -> Bool)
-> (Framebuffer -> Framebuffer -> Bool)
-> (Framebuffer -> Framebuffer -> Bool)
-> (Framebuffer -> Framebuffer -> Framebuffer)
-> (Framebuffer -> Framebuffer -> Framebuffer)
-> Ord Framebuffer
Framebuffer -> Framebuffer -> Bool
Framebuffer -> Framebuffer -> Ordering
Framebuffer -> Framebuffer -> Framebuffer
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 :: Framebuffer -> Framebuffer -> Framebuffer
$cmin :: Framebuffer -> Framebuffer -> Framebuffer
max :: Framebuffer -> Framebuffer -> Framebuffer
$cmax :: Framebuffer -> Framebuffer -> Framebuffer
>= :: Framebuffer -> Framebuffer -> Bool
$c>= :: Framebuffer -> Framebuffer -> Bool
> :: Framebuffer -> Framebuffer -> Bool
$c> :: Framebuffer -> Framebuffer -> Bool
<= :: Framebuffer -> Framebuffer -> Bool
$c<= :: Framebuffer -> Framebuffer -> Bool
< :: Framebuffer -> Framebuffer -> Bool
$c< :: Framebuffer -> Framebuffer -> Bool
compare :: Framebuffer -> Framebuffer -> Ordering
$ccompare :: Framebuffer -> Framebuffer -> Ordering
$cp1Ord :: Eq Framebuffer
Ord, Ptr b -> Int -> IO Framebuffer
Ptr b -> Int -> Framebuffer -> IO ()
Ptr Framebuffer -> IO Framebuffer
Ptr Framebuffer -> Int -> IO Framebuffer
Ptr Framebuffer -> Int -> Framebuffer -> IO ()
Ptr Framebuffer -> Framebuffer -> IO ()
Framebuffer -> Int
(Framebuffer -> Int)
-> (Framebuffer -> Int)
-> (Ptr Framebuffer -> Int -> IO Framebuffer)
-> (Ptr Framebuffer -> Int -> Framebuffer -> IO ())
-> (forall b. Ptr b -> Int -> IO Framebuffer)
-> (forall b. Ptr b -> Int -> Framebuffer -> IO ())
-> (Ptr Framebuffer -> IO Framebuffer)
-> (Ptr Framebuffer -> Framebuffer -> IO ())
-> Storable Framebuffer
forall b. Ptr b -> Int -> IO Framebuffer
forall b. Ptr b -> Int -> Framebuffer -> 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 Framebuffer -> Framebuffer -> IO ()
$cpoke :: Ptr Framebuffer -> Framebuffer -> IO ()
peek :: Ptr Framebuffer -> IO Framebuffer
$cpeek :: Ptr Framebuffer -> IO Framebuffer
pokeByteOff :: Ptr b -> Int -> Framebuffer -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Framebuffer -> IO ()
peekByteOff :: Ptr b -> Int -> IO Framebuffer
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Framebuffer
pokeElemOff :: Ptr Framebuffer -> Int -> Framebuffer -> IO ()
$cpokeElemOff :: Ptr Framebuffer -> Int -> Framebuffer -> IO ()
peekElemOff :: Ptr Framebuffer -> Int -> IO Framebuffer
$cpeekElemOff :: Ptr Framebuffer -> Int -> IO Framebuffer
alignment :: Framebuffer -> Int
$calignment :: Framebuffer -> Int
sizeOf :: Framebuffer -> Int
$csizeOf :: Framebuffer -> Int
Storable, Framebuffer
Framebuffer -> Zero Framebuffer
forall a. a -> Zero a
zero :: Framebuffer
$czero :: Framebuffer
Zero)
  deriving anyclass (Eq Framebuffer
Zero Framebuffer
(Eq Framebuffer, Zero Framebuffer) => IsHandle Framebuffer
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Framebuffer
$cp1IsHandle :: Eq Framebuffer
IsHandle)
instance HasObjectType Framebuffer where
  objectTypeAndHandle :: Framebuffer -> (ObjectType, Word64)
objectTypeAndHandle (Framebuffer h :: Word64
h) = (ObjectType
OBJECT_TYPE_FRAMEBUFFER, Word64
h)
instance Show Framebuffer where
  showsPrec :: Int -> Framebuffer -> ShowS
showsPrec p :: Int
p (Framebuffer x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Framebuffer 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)


-- | VkRenderPass - Opaque handle to a render pass object
--
-- = See Also
--
-- 'Vulkan.Core10.CommandBuffer.CommandBufferInheritanceInfo',
-- 'Vulkan.Core10.Pass.FramebufferCreateInfo',
-- 'Vulkan.Core10.Pipeline.GraphicsPipelineCreateInfo',
-- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo',
-- 'Vulkan.Core10.Pass.createRenderPass',
-- 'Vulkan.Core12.Promoted_From_VK_KHR_create_renderpass2.createRenderPass2',
-- 'Vulkan.Extensions.VK_KHR_create_renderpass2.createRenderPass2KHR',
-- 'Vulkan.Core10.Pass.destroyRenderPass',
-- 'Vulkan.Core10.Pass.getRenderAreaGranularity'
newtype RenderPass = RenderPass Word64
  deriving newtype (RenderPass -> RenderPass -> Bool
(RenderPass -> RenderPass -> Bool)
-> (RenderPass -> RenderPass -> Bool) -> Eq RenderPass
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RenderPass -> RenderPass -> Bool
$c/= :: RenderPass -> RenderPass -> Bool
== :: RenderPass -> RenderPass -> Bool
$c== :: RenderPass -> RenderPass -> Bool
Eq, Eq RenderPass
Eq RenderPass =>
(RenderPass -> RenderPass -> Ordering)
-> (RenderPass -> RenderPass -> Bool)
-> (RenderPass -> RenderPass -> Bool)
-> (RenderPass -> RenderPass -> Bool)
-> (RenderPass -> RenderPass -> Bool)
-> (RenderPass -> RenderPass -> RenderPass)
-> (RenderPass -> RenderPass -> RenderPass)
-> Ord RenderPass
RenderPass -> RenderPass -> Bool
RenderPass -> RenderPass -> Ordering
RenderPass -> RenderPass -> RenderPass
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 :: RenderPass -> RenderPass -> RenderPass
$cmin :: RenderPass -> RenderPass -> RenderPass
max :: RenderPass -> RenderPass -> RenderPass
$cmax :: RenderPass -> RenderPass -> RenderPass
>= :: RenderPass -> RenderPass -> Bool
$c>= :: RenderPass -> RenderPass -> Bool
> :: RenderPass -> RenderPass -> Bool
$c> :: RenderPass -> RenderPass -> Bool
<= :: RenderPass -> RenderPass -> Bool
$c<= :: RenderPass -> RenderPass -> Bool
< :: RenderPass -> RenderPass -> Bool
$c< :: RenderPass -> RenderPass -> Bool
compare :: RenderPass -> RenderPass -> Ordering
$ccompare :: RenderPass -> RenderPass -> Ordering
$cp1Ord :: Eq RenderPass
Ord, Ptr b -> Int -> IO RenderPass
Ptr b -> Int -> RenderPass -> IO ()
Ptr RenderPass -> IO RenderPass
Ptr RenderPass -> Int -> IO RenderPass
Ptr RenderPass -> Int -> RenderPass -> IO ()
Ptr RenderPass -> RenderPass -> IO ()
RenderPass -> Int
(RenderPass -> Int)
-> (RenderPass -> Int)
-> (Ptr RenderPass -> Int -> IO RenderPass)
-> (Ptr RenderPass -> Int -> RenderPass -> IO ())
-> (forall b. Ptr b -> Int -> IO RenderPass)
-> (forall b. Ptr b -> Int -> RenderPass -> IO ())
-> (Ptr RenderPass -> IO RenderPass)
-> (Ptr RenderPass -> RenderPass -> IO ())
-> Storable RenderPass
forall b. Ptr b -> Int -> IO RenderPass
forall b. Ptr b -> Int -> RenderPass -> 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 RenderPass -> RenderPass -> IO ()
$cpoke :: Ptr RenderPass -> RenderPass -> IO ()
peek :: Ptr RenderPass -> IO RenderPass
$cpeek :: Ptr RenderPass -> IO RenderPass
pokeByteOff :: Ptr b -> Int -> RenderPass -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> RenderPass -> IO ()
peekByteOff :: Ptr b -> Int -> IO RenderPass
$cpeekByteOff :: forall b. Ptr b -> Int -> IO RenderPass
pokeElemOff :: Ptr RenderPass -> Int -> RenderPass -> IO ()
$cpokeElemOff :: Ptr RenderPass -> Int -> RenderPass -> IO ()
peekElemOff :: Ptr RenderPass -> Int -> IO RenderPass
$cpeekElemOff :: Ptr RenderPass -> Int -> IO RenderPass
alignment :: RenderPass -> Int
$calignment :: RenderPass -> Int
sizeOf :: RenderPass -> Int
$csizeOf :: RenderPass -> Int
Storable, RenderPass
RenderPass -> Zero RenderPass
forall a. a -> Zero a
zero :: RenderPass
$czero :: RenderPass
Zero)
  deriving anyclass (Eq RenderPass
Zero RenderPass
(Eq RenderPass, Zero RenderPass) => IsHandle RenderPass
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero RenderPass
$cp1IsHandle :: Eq RenderPass
IsHandle)
instance HasObjectType RenderPass where
  objectTypeAndHandle :: RenderPass -> (ObjectType, Word64)
objectTypeAndHandle (RenderPass h :: Word64
h) = (ObjectType
OBJECT_TYPE_RENDER_PASS, Word64
h)
instance Show RenderPass where
  showsPrec :: Int -> RenderPass -> ShowS
showsPrec p :: Int
p (RenderPass x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "RenderPass 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)


-- | VkPipelineCache - Opaque handle to a pipeline cache object
--
-- = See Also
--
-- 'Vulkan.Core10.Pipeline.createComputePipelines',
-- 'Vulkan.Core10.Pipeline.createGraphicsPipelines',
-- 'Vulkan.Core10.PipelineCache.createPipelineCache',
-- 'Vulkan.Extensions.VK_KHR_ray_tracing.createRayTracingPipelinesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.createRayTracingPipelinesNV',
-- 'Vulkan.Core10.PipelineCache.destroyPipelineCache',
-- 'Vulkan.Core10.PipelineCache.getPipelineCacheData',
-- 'Vulkan.Core10.PipelineCache.mergePipelineCaches'
newtype PipelineCache = PipelineCache Word64
  deriving newtype (PipelineCache -> PipelineCache -> Bool
(PipelineCache -> PipelineCache -> Bool)
-> (PipelineCache -> PipelineCache -> Bool) -> Eq PipelineCache
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PipelineCache -> PipelineCache -> Bool
$c/= :: PipelineCache -> PipelineCache -> Bool
== :: PipelineCache -> PipelineCache -> Bool
$c== :: PipelineCache -> PipelineCache -> Bool
Eq, Eq PipelineCache
Eq PipelineCache =>
(PipelineCache -> PipelineCache -> Ordering)
-> (PipelineCache -> PipelineCache -> Bool)
-> (PipelineCache -> PipelineCache -> Bool)
-> (PipelineCache -> PipelineCache -> Bool)
-> (PipelineCache -> PipelineCache -> Bool)
-> (PipelineCache -> PipelineCache -> PipelineCache)
-> (PipelineCache -> PipelineCache -> PipelineCache)
-> Ord PipelineCache
PipelineCache -> PipelineCache -> Bool
PipelineCache -> PipelineCache -> Ordering
PipelineCache -> PipelineCache -> PipelineCache
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 :: PipelineCache -> PipelineCache -> PipelineCache
$cmin :: PipelineCache -> PipelineCache -> PipelineCache
max :: PipelineCache -> PipelineCache -> PipelineCache
$cmax :: PipelineCache -> PipelineCache -> PipelineCache
>= :: PipelineCache -> PipelineCache -> Bool
$c>= :: PipelineCache -> PipelineCache -> Bool
> :: PipelineCache -> PipelineCache -> Bool
$c> :: PipelineCache -> PipelineCache -> Bool
<= :: PipelineCache -> PipelineCache -> Bool
$c<= :: PipelineCache -> PipelineCache -> Bool
< :: PipelineCache -> PipelineCache -> Bool
$c< :: PipelineCache -> PipelineCache -> Bool
compare :: PipelineCache -> PipelineCache -> Ordering
$ccompare :: PipelineCache -> PipelineCache -> Ordering
$cp1Ord :: Eq PipelineCache
Ord, Ptr b -> Int -> IO PipelineCache
Ptr b -> Int -> PipelineCache -> IO ()
Ptr PipelineCache -> IO PipelineCache
Ptr PipelineCache -> Int -> IO PipelineCache
Ptr PipelineCache -> Int -> PipelineCache -> IO ()
Ptr PipelineCache -> PipelineCache -> IO ()
PipelineCache -> Int
(PipelineCache -> Int)
-> (PipelineCache -> Int)
-> (Ptr PipelineCache -> Int -> IO PipelineCache)
-> (Ptr PipelineCache -> Int -> PipelineCache -> IO ())
-> (forall b. Ptr b -> Int -> IO PipelineCache)
-> (forall b. Ptr b -> Int -> PipelineCache -> IO ())
-> (Ptr PipelineCache -> IO PipelineCache)
-> (Ptr PipelineCache -> PipelineCache -> IO ())
-> Storable PipelineCache
forall b. Ptr b -> Int -> IO PipelineCache
forall b. Ptr b -> Int -> PipelineCache -> 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 PipelineCache -> PipelineCache -> IO ()
$cpoke :: Ptr PipelineCache -> PipelineCache -> IO ()
peek :: Ptr PipelineCache -> IO PipelineCache
$cpeek :: Ptr PipelineCache -> IO PipelineCache
pokeByteOff :: Ptr b -> Int -> PipelineCache -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PipelineCache -> IO ()
peekByteOff :: Ptr b -> Int -> IO PipelineCache
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PipelineCache
pokeElemOff :: Ptr PipelineCache -> Int -> PipelineCache -> IO ()
$cpokeElemOff :: Ptr PipelineCache -> Int -> PipelineCache -> IO ()
peekElemOff :: Ptr PipelineCache -> Int -> IO PipelineCache
$cpeekElemOff :: Ptr PipelineCache -> Int -> IO PipelineCache
alignment :: PipelineCache -> Int
$calignment :: PipelineCache -> Int
sizeOf :: PipelineCache -> Int
$csizeOf :: PipelineCache -> Int
Storable, PipelineCache
PipelineCache -> Zero PipelineCache
forall a. a -> Zero a
zero :: PipelineCache
$czero :: PipelineCache
Zero)
  deriving anyclass (Eq PipelineCache
Zero PipelineCache
(Eq PipelineCache, Zero PipelineCache) => IsHandle PipelineCache
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero PipelineCache
$cp1IsHandle :: Eq PipelineCache
IsHandle)
instance HasObjectType PipelineCache where
  objectTypeAndHandle :: PipelineCache -> (ObjectType, Word64)
objectTypeAndHandle (PipelineCache h :: Word64
h) = (ObjectType
OBJECT_TYPE_PIPELINE_CACHE, Word64
h)
instance Show PipelineCache where
  showsPrec :: Int -> PipelineCache -> ShowS
showsPrec p :: Int
p (PipelineCache x :: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PipelineCache 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)