{-# language CPP #-}
module Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2  ( getPhysicalDeviceFeatures2
                                                                           , getPhysicalDeviceProperties2
                                                                           , getPhysicalDeviceFormatProperties2
                                                                           , getPhysicalDeviceImageFormatProperties2
                                                                           , getPhysicalDeviceQueueFamilyProperties2
                                                                           , getPhysicalDeviceMemoryProperties2
                                                                           , getPhysicalDeviceSparseImageFormatProperties2
                                                                           , PhysicalDeviceFeatures2(..)
                                                                           , PhysicalDeviceProperties2(..)
                                                                           , FormatProperties2(..)
                                                                           , ImageFormatProperties2(..)
                                                                           , PhysicalDeviceImageFormatInfo2(..)
                                                                           , QueueFamilyProperties2(..)
                                                                           , PhysicalDeviceMemoryProperties2(..)
                                                                           , SparseImageFormatProperties2(..)
                                                                           , PhysicalDeviceSparseImageFormatInfo2(..)
                                                                           , StructureType(..)
                                                                           ) where

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.NamedType ((:::))
import {-# SOURCE #-} Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer (AndroidHardwareBufferUsageANDROID)
import Vulkan.CStruct.Extends (Chain)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_image_drm_format_modifier (DrmFormatModifierPropertiesListEXT)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities (ExternalImageFormatProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_filter_cubic (FilterCubicImageViewImageFormatPropertiesEXT)
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.Core10.Enums.Format (Format(..))
import Vulkan.Core10.DeviceInitialization (FormatProperties)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.ImageCreateFlagBits (ImageCreateFlags)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_image_format_list (ImageFormatListCreateInfo)
import Vulkan.Core10.DeviceInitialization (ImageFormatProperties)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage (ImageStencilUsageCreateInfo)
import Vulkan.Core10.Enums.ImageTiling (ImageTiling)
import Vulkan.Core10.Enums.ImageType (ImageType)
import Vulkan.Core10.Enums.ImageUsageFlagBits (ImageUsageFlags)
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceFeatures2))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceFormatProperties2))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceImageFormatProperties2))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceMemoryProperties2))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceProperties2))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceQueueFamilyProperties2))
import Vulkan.Dynamic (InstanceCmds(pVkGetPhysicalDeviceSparseImageFormatProperties2))
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Handles (PhysicalDevice)
import Vulkan.Core10.Handles (PhysicalDevice(..))
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_16bit_storage (PhysicalDevice16BitStorageFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_4444_formats (PhysicalDevice4444FormatsFeaturesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_8bit_storage (PhysicalDevice8BitStorageFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_astc_decode_mode (PhysicalDeviceASTCDecodeFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_blend_operation_advanced (PhysicalDeviceBlendOperationAdvancedFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_blend_operation_advanced (PhysicalDeviceBlendOperationAdvancedPropertiesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address (PhysicalDeviceBufferDeviceAddressFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_buffer_device_address (PhysicalDeviceBufferDeviceAddressFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_AMD_device_coherent_memory (PhysicalDeviceCoherentMemoryFeaturesAMD)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_compute_shader_derivatives (PhysicalDeviceComputeShaderDerivativesFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_conditional_rendering (PhysicalDeviceConditionalRenderingFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_conservative_rasterization (PhysicalDeviceConservativeRasterizationPropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_cooperative_matrix (PhysicalDeviceCooperativeMatrixFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_cooperative_matrix (PhysicalDeviceCooperativeMatrixPropertiesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_corner_sampled_image (PhysicalDeviceCornerSampledImageFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_coverage_reduction_mode (PhysicalDeviceCoverageReductionModeFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_custom_border_color (PhysicalDeviceCustomBorderColorFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_custom_border_color (PhysicalDeviceCustomBorderColorPropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_dedicated_allocation_image_aliasing (PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_depth_clip_enable (PhysicalDeviceDepthClipEnableFeaturesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve (PhysicalDeviceDepthStencilResolveProperties)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing (PhysicalDeviceDescriptorIndexingFeatures)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing (PhysicalDeviceDescriptorIndexingProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_device_generated_commands (PhysicalDeviceDeviceGeneratedCommandsFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_device_generated_commands (PhysicalDeviceDeviceGeneratedCommandsPropertiesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_device_memory_report (PhysicalDeviceDeviceMemoryReportFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_device_diagnostics_config (PhysicalDeviceDiagnosticsConfigFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_discard_rectangles (PhysicalDeviceDiscardRectanglePropertiesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_driver_properties (PhysicalDeviceDriverProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_scissor_exclusive (PhysicalDeviceExclusiveScissorFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_extended_dynamic_state (PhysicalDeviceExtendedDynamicStateFeaturesEXT)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities (PhysicalDeviceExternalImageFormatInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_external_memory_host (PhysicalDeviceExternalMemoryHostPropertiesEXT)
import Vulkan.Core10.DeviceInitialization (PhysicalDeviceFeatures)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_shader_float_controls (PhysicalDeviceFloatControlsProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map2 (PhysicalDeviceFragmentDensityMap2FeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map2 (PhysicalDeviceFragmentDensityMap2PropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map (PhysicalDeviceFragmentDensityMapFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map (PhysicalDeviceFragmentDensityMapPropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_fragment_shader_barycentric (PhysicalDeviceFragmentShaderBarycentricFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_shader_interlock (PhysicalDeviceFragmentShaderInterlockFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_fragment_shading_rate (PhysicalDeviceFragmentShadingRateFeaturesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_fragment_shading_rate (PhysicalDeviceFragmentShadingRatePropertiesKHR)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset (PhysicalDeviceHostQueryResetFeatures)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities (PhysicalDeviceIDProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_image_drm_format_modifier (PhysicalDeviceImageDrmFormatModifierInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_image_robustness (PhysicalDeviceImageRobustnessFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_filter_cubic (PhysicalDeviceImageViewImageFormatInfoEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer (PhysicalDeviceImagelessFramebufferFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_index_type_uint8 (PhysicalDeviceIndexTypeUint8FeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_inline_uniform_block (PhysicalDeviceInlineUniformBlockFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_inline_uniform_block (PhysicalDeviceInlineUniformBlockPropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_line_rasterization (PhysicalDeviceLineRasterizationFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_line_rasterization (PhysicalDeviceLineRasterizationPropertiesEXT)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_maintenance3 (PhysicalDeviceMaintenance3Properties)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_memory_budget (PhysicalDeviceMemoryBudgetPropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_memory_priority (PhysicalDeviceMemoryPriorityFeaturesEXT)
import Vulkan.Core10.DeviceInitialization (PhysicalDeviceMemoryProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_mesh_shader (PhysicalDeviceMeshShaderFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_mesh_shader (PhysicalDeviceMeshShaderPropertiesNV)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_multiview (PhysicalDeviceMultiviewFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_NVX_multiview_per_view_attributes (PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_multiview (PhysicalDeviceMultiviewProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_pci_bus_info (PhysicalDevicePCIBusInfoPropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_performance_query (PhysicalDevicePerformanceQueryFeaturesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_performance_query (PhysicalDevicePerformanceQueryPropertiesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_pipeline_creation_cache_control (PhysicalDevicePipelineCreationCacheControlFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_pipeline_executable_properties (PhysicalDevicePipelineExecutablePropertiesFeaturesKHR)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_maintenance2 (PhysicalDevicePointClippingProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_portability_subset (PhysicalDevicePortabilitySubsetFeaturesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_portability_subset (PhysicalDevicePortabilitySubsetPropertiesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_private_data (PhysicalDevicePrivateDataFeaturesEXT)
import Vulkan.Core10.DeviceInitialization (PhysicalDeviceProperties)
import {-# SOURCE #-} Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory (PhysicalDeviceProtectedMemoryFeatures)
import {-# SOURCE #-} Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory (PhysicalDeviceProtectedMemoryProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_push_descriptor (PhysicalDevicePushDescriptorPropertiesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_ray_tracing (PhysicalDeviceRayTracingFeaturesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_ray_tracing (PhysicalDeviceRayTracingPropertiesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_ray_tracing (PhysicalDeviceRayTracingPropertiesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_representative_fragment_test (PhysicalDeviceRepresentativeFragmentTestFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_robustness2 (PhysicalDeviceRobustness2FeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_robustness2 (PhysicalDeviceRobustness2PropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_sample_locations (PhysicalDeviceSampleLocationsPropertiesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax (PhysicalDeviceSamplerFilterMinmaxProperties)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion (PhysicalDeviceSamplerYcbcrConversionFeatures)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_scalar_block_layout (PhysicalDeviceScalarBlockLayoutFeatures)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts (PhysicalDeviceSeparateDepthStencilLayoutsFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_shader_atomic_float (PhysicalDeviceShaderAtomicFloatFeaturesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_shader_atomic_int64 (PhysicalDeviceShaderAtomicInt64Features)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_shader_clock (PhysicalDeviceShaderClockFeaturesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_AMD_shader_core_properties2 (PhysicalDeviceShaderCoreProperties2AMD)
import {-# SOURCE #-} Vulkan.Extensions.VK_AMD_shader_core_properties (PhysicalDeviceShaderCorePropertiesAMD)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_shader_demote_to_helper_invocation (PhysicalDeviceShaderDemoteToHelperInvocationFeaturesEXT)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_shader_draw_parameters (PhysicalDeviceShaderDrawParametersFeatures)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_shader_float16_int8 (PhysicalDeviceShaderFloat16Int8Features)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_shader_image_atomic_int64 (PhysicalDeviceShaderImageAtomicInt64FeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_shader_image_footprint (PhysicalDeviceShaderImageFootprintFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_INTEL_shader_integer_functions2 (PhysicalDeviceShaderIntegerFunctions2FeaturesINTEL)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_shader_sm_builtins (PhysicalDeviceShaderSMBuiltinsFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_shader_sm_builtins (PhysicalDeviceShaderSMBuiltinsPropertiesNV)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_shader_subgroup_extended_types (PhysicalDeviceShaderSubgroupExtendedTypesFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_shader_terminate_invocation (PhysicalDeviceShaderTerminateInvocationFeaturesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_shading_rate_image (PhysicalDeviceShadingRateImageFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_shading_rate_image (PhysicalDeviceShadingRateImagePropertiesNV)
import {-# SOURCE #-} Vulkan.Core11.Originally_Based_On_VK_KHR_subgroup (PhysicalDeviceSubgroupProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_subgroup_size_control (PhysicalDeviceSubgroupSizeControlFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_subgroup_size_control (PhysicalDeviceSubgroupSizeControlPropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_texel_buffer_alignment (PhysicalDeviceTexelBufferAlignmentFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_texel_buffer_alignment (PhysicalDeviceTexelBufferAlignmentPropertiesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_texture_compression_astc_hdr (PhysicalDeviceTextureCompressionASTCHDRFeaturesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore (PhysicalDeviceTimelineSemaphoreFeatures)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore (PhysicalDeviceTimelineSemaphoreProperties)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_transform_feedback (PhysicalDeviceTransformFeedbackFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_transform_feedback (PhysicalDeviceTransformFeedbackPropertiesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_uniform_buffer_standard_layout (PhysicalDeviceUniformBufferStandardLayoutFeatures)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_variable_pointers (PhysicalDeviceVariablePointersFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_vertex_attribute_divisor (PhysicalDeviceVertexAttributeDivisorFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_vertex_attribute_divisor (PhysicalDeviceVertexAttributeDivisorPropertiesEXT)
import {-# SOURCE #-} Vulkan.Core12 (PhysicalDeviceVulkan11Features)
import {-# SOURCE #-} Vulkan.Core12 (PhysicalDeviceVulkan11Properties)
import {-# SOURCE #-} Vulkan.Core12 (PhysicalDeviceVulkan12Features)
import {-# SOURCE #-} Vulkan.Core12 (PhysicalDeviceVulkan12Properties)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_vulkan_memory_model (PhysicalDeviceVulkanMemoryModelFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_ycbcr_image_arrays (PhysicalDeviceYcbcrImageArraysFeaturesEXT)
import Vulkan.Core10.Handles (PhysicalDevice_T)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_device_diagnostic_checkpoints (QueueFamilyCheckpointPropertiesNV)
import Vulkan.Core10.DeviceInitialization (QueueFamilyProperties)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.SampleCountFlagBits (SampleCountFlagBits)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion (SamplerYcbcrConversionImageFormatProperties)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.SparseResourceMemoryManagement (SparseImageFormatProperties)
import Vulkan.Core10.Enums.StructureType (StructureType)
import {-# SOURCE #-} Vulkan.Extensions.VK_AMD_texture_gather_bias_lod (TextureLODGatherFormatPropertiesAMD)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FORMAT_PROPERTIES_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_IMAGE_FORMAT_PROPERTIES_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_FEATURES_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_FORMAT_INFO_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PROPERTIES_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_PROPERTIES_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_SPARSE_IMAGE_FORMAT_INFO_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_QUEUE_FAMILY_PROPERTIES_2))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SPARSE_IMAGE_FORMAT_PROPERTIES_2))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Enums.StructureType (StructureType(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceFeatures2
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceFeatures2) -> IO ()) -> Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceFeatures2) -> IO ()

-- | vkGetPhysicalDeviceFeatures2 - Reports capabilities of a physical device
--
-- = Description
--
-- Each structure in @pFeatures@ and its @pNext@ chain contains members
-- corresponding to fine-grained features. 'getPhysicalDeviceFeatures2'
-- writes each member to a boolean value indicating whether that feature is
-- supported.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'PhysicalDeviceFeatures2'
getPhysicalDeviceFeatures2 :: forall a io
                            . (Extendss PhysicalDeviceFeatures2 a, PokeChain a, PeekChain a, MonadIO io)
                           => -- | @physicalDevice@ is the physical device from which to query the
                              -- supported features.
                              --
                              -- @physicalDevice@ /must/ be a valid
                              -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                              PhysicalDevice
                           -> io (PhysicalDeviceFeatures2 a)
getPhysicalDeviceFeatures2 :: PhysicalDevice -> io (PhysicalDeviceFeatures2 a)
getPhysicalDeviceFeatures2 physicalDevice :: PhysicalDevice
physicalDevice = IO (PhysicalDeviceFeatures2 a) -> io (PhysicalDeviceFeatures2 a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (PhysicalDeviceFeatures2 a) -> io (PhysicalDeviceFeatures2 a))
-> (ContT
      (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a)
    -> IO (PhysicalDeviceFeatures2 a))
-> ContT (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a)
-> io (PhysicalDeviceFeatures2 a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a)
-> IO (PhysicalDeviceFeatures2 a)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a)
 -> io (PhysicalDeviceFeatures2 a))
-> ContT (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a)
-> io (PhysicalDeviceFeatures2 a)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceFeatures2Ptr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
   -> IO ())
vkGetPhysicalDeviceFeatures2Ptr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
      -> IO ())
pVkGetPhysicalDeviceFeatures2 (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT (PhysicalDeviceFeatures2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (PhysicalDeviceFeatures2 a) IO ())
-> IO () -> ContT (PhysicalDeviceFeatures2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
   -> IO ())
vkGetPhysicalDeviceFeatures2Ptr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
   -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceFeatures2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceFeatures2' :: Ptr PhysicalDevice_T
-> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
-> IO ()
vkGetPhysicalDeviceFeatures2' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
   -> IO ())
-> Ptr PhysicalDevice_T
-> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
-> IO ()
mkVkGetPhysicalDeviceFeatures2 FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
   -> IO ())
vkGetPhysicalDeviceFeatures2Ptr
  Ptr (PhysicalDeviceFeatures2 a)
pPFeatures <- ((Ptr (PhysicalDeviceFeatures2 a)
  -> IO (PhysicalDeviceFeatures2 a))
 -> IO (PhysicalDeviceFeatures2 a))
-> ContT
     (PhysicalDeviceFeatures2 a) IO (Ptr (PhysicalDeviceFeatures2 a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct (PhysicalDeviceFeatures2 a) =>
(Ptr (PhysicalDeviceFeatures2 a) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(PhysicalDeviceFeatures2 _))
  IO () -> ContT (PhysicalDeviceFeatures2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (PhysicalDeviceFeatures2 a) IO ())
-> IO () -> ContT (PhysicalDeviceFeatures2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2))
-> IO ()
vkGetPhysicalDeviceFeatures2' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) (Ptr (PhysicalDeviceFeatures2 a)
-> "pFeatures" ::: Ptr (SomeStruct PhysicalDeviceFeatures2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PhysicalDeviceFeatures2 a)
pPFeatures))
  PhysicalDeviceFeatures2 a
pFeatures <- IO (PhysicalDeviceFeatures2 a)
-> ContT (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (PhysicalDeviceFeatures2 a)
 -> ContT
      (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a))
-> IO (PhysicalDeviceFeatures2 a)
-> ContT (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a)
forall a b. (a -> b) -> a -> b
$ Ptr (PhysicalDeviceFeatures2 a) -> IO (PhysicalDeviceFeatures2 a)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(PhysicalDeviceFeatures2 _) Ptr (PhysicalDeviceFeatures2 a)
pPFeatures
  PhysicalDeviceFeatures2 a
-> ContT (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceFeatures2 a
 -> ContT
      (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a))
-> PhysicalDeviceFeatures2 a
-> ContT (PhysicalDeviceFeatures2 a) IO (PhysicalDeviceFeatures2 a)
forall a b. (a -> b) -> a -> b
$ (PhysicalDeviceFeatures2 a
pFeatures)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceProperties2
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceProperties2) -> IO ()) -> Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceProperties2) -> IO ()

-- | vkGetPhysicalDeviceProperties2 - Returns properties of a physical device
--
-- = Description
--
-- Each structure in @pProperties@ and its @pNext@ chain contain members
-- corresponding to properties or implementation-dependent limits.
-- 'getPhysicalDeviceProperties2' writes each member to a value indicating
-- the value of that property or limit.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'PhysicalDeviceProperties2'
getPhysicalDeviceProperties2 :: forall a io
                              . (Extendss PhysicalDeviceProperties2 a, PokeChain a, PeekChain a, MonadIO io)
                             => -- | @physicalDevice@ is the handle to the physical device whose properties
                                -- will be queried.
                                --
                                -- @physicalDevice@ /must/ be a valid
                                -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                                PhysicalDevice
                             -> io (PhysicalDeviceProperties2 a)
getPhysicalDeviceProperties2 :: PhysicalDevice -> io (PhysicalDeviceProperties2 a)
getPhysicalDeviceProperties2 physicalDevice :: PhysicalDevice
physicalDevice = IO (PhysicalDeviceProperties2 a)
-> io (PhysicalDeviceProperties2 a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (PhysicalDeviceProperties2 a)
 -> io (PhysicalDeviceProperties2 a))
-> (ContT
      (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a)
    -> IO (PhysicalDeviceProperties2 a))
-> ContT
     (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a)
-> io (PhysicalDeviceProperties2 a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a)
-> IO (PhysicalDeviceProperties2 a)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a)
 -> io (PhysicalDeviceProperties2 a))
-> ContT
     (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a)
-> io (PhysicalDeviceProperties2 a)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceProperties2Ptr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
   -> IO ())
vkGetPhysicalDeviceProperties2Ptr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
      -> IO ())
pVkGetPhysicalDeviceProperties2 (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT (PhysicalDeviceProperties2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (PhysicalDeviceProperties2 a) IO ())
-> IO () -> ContT (PhysicalDeviceProperties2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
   -> IO ())
vkGetPhysicalDeviceProperties2Ptr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
   -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceProperties2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceProperties2' :: Ptr PhysicalDevice_T
-> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
-> IO ()
vkGetPhysicalDeviceProperties2' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
   -> IO ())
-> Ptr PhysicalDevice_T
-> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
-> IO ()
mkVkGetPhysicalDeviceProperties2 FunPtr
  (Ptr PhysicalDevice_T
   -> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
   -> IO ())
vkGetPhysicalDeviceProperties2Ptr
  Ptr (PhysicalDeviceProperties2 a)
pPProperties <- ((Ptr (PhysicalDeviceProperties2 a)
  -> IO (PhysicalDeviceProperties2 a))
 -> IO (PhysicalDeviceProperties2 a))
-> ContT
     (PhysicalDeviceProperties2 a)
     IO
     (Ptr (PhysicalDeviceProperties2 a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct (PhysicalDeviceProperties2 a) =>
(Ptr (PhysicalDeviceProperties2 a) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(PhysicalDeviceProperties2 _))
  IO () -> ContT (PhysicalDeviceProperties2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (PhysicalDeviceProperties2 a) IO ())
-> IO () -> ContT (PhysicalDeviceProperties2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2))
-> IO ()
vkGetPhysicalDeviceProperties2' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) (Ptr (PhysicalDeviceProperties2 a)
-> "pProperties" ::: Ptr (SomeStruct PhysicalDeviceProperties2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PhysicalDeviceProperties2 a)
pPProperties))
  PhysicalDeviceProperties2 a
pProperties <- IO (PhysicalDeviceProperties2 a)
-> ContT
     (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (PhysicalDeviceProperties2 a)
 -> ContT
      (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a))
-> IO (PhysicalDeviceProperties2 a)
-> ContT
     (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a)
forall a b. (a -> b) -> a -> b
$ Ptr (PhysicalDeviceProperties2 a)
-> IO (PhysicalDeviceProperties2 a)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(PhysicalDeviceProperties2 _) Ptr (PhysicalDeviceProperties2 a)
pPProperties
  PhysicalDeviceProperties2 a
-> ContT
     (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceProperties2 a
 -> ContT
      (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a))
-> PhysicalDeviceProperties2 a
-> ContT
     (PhysicalDeviceProperties2 a) IO (PhysicalDeviceProperties2 a)
forall a b. (a -> b) -> a -> b
$ (PhysicalDeviceProperties2 a
pProperties)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceFormatProperties2
  :: FunPtr (Ptr PhysicalDevice_T -> Format -> Ptr (SomeStruct FormatProperties2) -> IO ()) -> Ptr PhysicalDevice_T -> Format -> Ptr (SomeStruct FormatProperties2) -> IO ()

-- | vkGetPhysicalDeviceFormatProperties2 - Lists physical device’s format
-- capabilities
--
-- = Description
--
-- 'getPhysicalDeviceFormatProperties2' behaves similarly to
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceFormatProperties',
-- with the ability to return extended information in a @pNext@ chain of
-- output structures.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.Format.Format', 'FormatProperties2',
-- 'Vulkan.Core10.Handles.PhysicalDevice'
getPhysicalDeviceFormatProperties2 :: forall a io
                                    . (Extendss FormatProperties2 a, PokeChain a, PeekChain a, MonadIO io)
                                   => -- | @physicalDevice@ is the physical device from which to query the format
                                      -- properties.
                                      --
                                      -- @physicalDevice@ /must/ be a valid
                                      -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                                      PhysicalDevice
                                   -> -- | @format@ is the format whose properties are queried.
                                      --
                                      -- @format@ /must/ be a valid 'Vulkan.Core10.Enums.Format.Format' value
                                      Format
                                   -> io (FormatProperties2 a)
getPhysicalDeviceFormatProperties2 :: PhysicalDevice -> Format -> io (FormatProperties2 a)
getPhysicalDeviceFormatProperties2 physicalDevice :: PhysicalDevice
physicalDevice format :: Format
format = IO (FormatProperties2 a) -> io (FormatProperties2 a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (FormatProperties2 a) -> io (FormatProperties2 a))
-> (ContT (FormatProperties2 a) IO (FormatProperties2 a)
    -> IO (FormatProperties2 a))
-> ContT (FormatProperties2 a) IO (FormatProperties2 a)
-> io (FormatProperties2 a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (FormatProperties2 a) IO (FormatProperties2 a)
-> IO (FormatProperties2 a)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (FormatProperties2 a) IO (FormatProperties2 a)
 -> io (FormatProperties2 a))
-> ContT (FormatProperties2 a) IO (FormatProperties2 a)
-> io (FormatProperties2 a)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceFormatProperties2Ptr :: FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
   -> IO ())
vkGetPhysicalDeviceFormatProperties2Ptr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> Format
      -> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
      -> IO ())
pVkGetPhysicalDeviceFormatProperties2 (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT (FormatProperties2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (FormatProperties2 a) IO ())
-> IO () -> ContT (FormatProperties2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
   -> IO ())
vkGetPhysicalDeviceFormatProperties2Ptr FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
   -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> Format
      -> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceFormatProperties2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceFormatProperties2' :: Ptr PhysicalDevice_T
-> Format
-> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
-> IO ()
vkGetPhysicalDeviceFormatProperties2' = FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
   -> IO ())
-> Ptr PhysicalDevice_T
-> Format
-> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
-> IO ()
mkVkGetPhysicalDeviceFormatProperties2 FunPtr
  (Ptr PhysicalDevice_T
   -> Format
   -> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
   -> IO ())
vkGetPhysicalDeviceFormatProperties2Ptr
  Ptr (FormatProperties2 a)
pPFormatProperties <- ((Ptr (FormatProperties2 a) -> IO (FormatProperties2 a))
 -> IO (FormatProperties2 a))
-> ContT (FormatProperties2 a) IO (Ptr (FormatProperties2 a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct (FormatProperties2 a) =>
(Ptr (FormatProperties2 a) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(FormatProperties2 _))
  IO () -> ContT (FormatProperties2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (FormatProperties2 a) IO ())
-> IO () -> ContT (FormatProperties2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> Format
-> ("pFormatProperties" ::: Ptr (SomeStruct FormatProperties2))
-> IO ()
vkGetPhysicalDeviceFormatProperties2' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) (Format
format) (Ptr (FormatProperties2 a)
-> "pFormatProperties" ::: Ptr (SomeStruct FormatProperties2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (FormatProperties2 a)
pPFormatProperties))
  FormatProperties2 a
pFormatProperties <- IO (FormatProperties2 a)
-> ContT (FormatProperties2 a) IO (FormatProperties2 a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (FormatProperties2 a)
 -> ContT (FormatProperties2 a) IO (FormatProperties2 a))
-> IO (FormatProperties2 a)
-> ContT (FormatProperties2 a) IO (FormatProperties2 a)
forall a b. (a -> b) -> a -> b
$ Ptr (FormatProperties2 a) -> IO (FormatProperties2 a)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(FormatProperties2 _) Ptr (FormatProperties2 a)
pPFormatProperties
  FormatProperties2 a
-> ContT (FormatProperties2 a) IO (FormatProperties2 a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FormatProperties2 a
 -> ContT (FormatProperties2 a) IO (FormatProperties2 a))
-> FormatProperties2 a
-> ContT (FormatProperties2 a) IO (FormatProperties2 a)
forall a b. (a -> b) -> a -> b
$ (FormatProperties2 a
pFormatProperties)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceImageFormatProperties2
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceImageFormatInfo2) -> Ptr (SomeStruct ImageFormatProperties2) -> IO Result) -> Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceImageFormatInfo2) -> Ptr (SomeStruct ImageFormatProperties2) -> IO Result

-- | vkGetPhysicalDeviceImageFormatProperties2 - Lists physical device’s
-- image format capabilities
--
-- = Description
--
-- 'getPhysicalDeviceImageFormatProperties2' behaves similarly to
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceImageFormatProperties',
-- with the ability to return extended information in a @pNext@ chain of
-- output structures.
--
-- == Valid Usage
--
-- -   If the @pNext@ chain of @pImageFormatProperties@ includes a
--     'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AndroidHardwareBufferUsageANDROID'
--     structure, the @pNext@ chain of @pImageFormatInfo@ /must/ include a
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.PhysicalDeviceExternalImageFormatInfo'
--     structure with @handleType@ set to
--     'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID'
--
-- == Valid Usage (Implicit)
--
-- -   @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   @pImageFormatInfo@ /must/ be a valid pointer to a valid
--     'PhysicalDeviceImageFormatInfo2' structure
--
-- -   @pImageFormatProperties@ /must/ be a valid pointer to a
--     'ImageFormatProperties2' structure
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_FORMAT_NOT_SUPPORTED'
--
-- = See Also
--
-- 'ImageFormatProperties2', 'Vulkan.Core10.Handles.PhysicalDevice',
-- 'PhysicalDeviceImageFormatInfo2'
getPhysicalDeviceImageFormatProperties2 :: forall a b io
                                         . (Extendss PhysicalDeviceImageFormatInfo2 a, Extendss ImageFormatProperties2 b, PokeChain a, PokeChain b, PeekChain b, MonadIO io)
                                        => -- | @physicalDevice@ is the physical device from which to query the image
                                           -- capabilities.
                                           PhysicalDevice
                                        -> -- | @pImageFormatInfo@ is a pointer to a 'PhysicalDeviceImageFormatInfo2'
                                           -- structure describing the parameters that would be consumed by
                                           -- 'Vulkan.Core10.Image.createImage'.
                                           (PhysicalDeviceImageFormatInfo2 a)
                                        -> io (ImageFormatProperties2 b)
getPhysicalDeviceImageFormatProperties2 :: PhysicalDevice
-> PhysicalDeviceImageFormatInfo2 a
-> io (ImageFormatProperties2 b)
getPhysicalDeviceImageFormatProperties2 physicalDevice :: PhysicalDevice
physicalDevice imageFormatInfo :: PhysicalDeviceImageFormatInfo2 a
imageFormatInfo = IO (ImageFormatProperties2 b) -> io (ImageFormatProperties2 b)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (ImageFormatProperties2 b) -> io (ImageFormatProperties2 b))
-> (ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b)
    -> IO (ImageFormatProperties2 b))
-> ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b)
-> io (ImageFormatProperties2 b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b)
-> IO (ImageFormatProperties2 b)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b)
 -> io (ImageFormatProperties2 b))
-> ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b)
-> io (ImageFormatProperties2 b)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceImageFormatProperties2Ptr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pImageFormatInfo"
       ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
   -> ("pImageFormatProperties"
       ::: Ptr (SomeStruct ImageFormatProperties2))
   -> IO Result)
vkGetPhysicalDeviceImageFormatProperties2Ptr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pImageFormatInfo"
          ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
      -> ("pImageFormatProperties"
          ::: Ptr (SomeStruct ImageFormatProperties2))
      -> IO Result)
pVkGetPhysicalDeviceImageFormatProperties2 (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT (ImageFormatProperties2 b) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (ImageFormatProperties2 b) IO ())
-> IO () -> ContT (ImageFormatProperties2 b) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pImageFormatInfo"
       ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
   -> ("pImageFormatProperties"
       ::: Ptr (SomeStruct ImageFormatProperties2))
   -> IO Result)
vkGetPhysicalDeviceImageFormatProperties2Ptr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pImageFormatInfo"
       ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
   -> ("pImageFormatProperties"
       ::: Ptr (SomeStruct ImageFormatProperties2))
   -> IO Result)
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pImageFormatInfo"
          ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
      -> ("pImageFormatProperties"
          ::: Ptr (SomeStruct ImageFormatProperties2))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pImageFormatInfo"
       ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
   -> ("pImageFormatProperties"
       ::: Ptr (SomeStruct ImageFormatProperties2))
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceImageFormatProperties2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceImageFormatProperties2' :: Ptr PhysicalDevice_T
-> ("pImageFormatInfo"
    ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
-> ("pImageFormatProperties"
    ::: Ptr (SomeStruct ImageFormatProperties2))
-> IO Result
vkGetPhysicalDeviceImageFormatProperties2' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pImageFormatInfo"
       ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
   -> ("pImageFormatProperties"
       ::: Ptr (SomeStruct ImageFormatProperties2))
   -> IO Result)
-> Ptr PhysicalDevice_T
-> ("pImageFormatInfo"
    ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
-> ("pImageFormatProperties"
    ::: Ptr (SomeStruct ImageFormatProperties2))
-> IO Result
mkVkGetPhysicalDeviceImageFormatProperties2 FunPtr
  (Ptr PhysicalDevice_T
   -> ("pImageFormatInfo"
       ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
   -> ("pImageFormatProperties"
       ::: Ptr (SomeStruct ImageFormatProperties2))
   -> IO Result)
vkGetPhysicalDeviceImageFormatProperties2Ptr
  Ptr (PhysicalDeviceImageFormatInfo2 a)
pImageFormatInfo <- ((Ptr (PhysicalDeviceImageFormatInfo2 a)
  -> IO (ImageFormatProperties2 b))
 -> IO (ImageFormatProperties2 b))
-> ContT
     (ImageFormatProperties2 b)
     IO
     (Ptr (PhysicalDeviceImageFormatInfo2 a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (PhysicalDeviceImageFormatInfo2 a)
   -> IO (ImageFormatProperties2 b))
  -> IO (ImageFormatProperties2 b))
 -> ContT
      (ImageFormatProperties2 b)
      IO
      (Ptr (PhysicalDeviceImageFormatInfo2 a)))
-> ((Ptr (PhysicalDeviceImageFormatInfo2 a)
     -> IO (ImageFormatProperties2 b))
    -> IO (ImageFormatProperties2 b))
-> ContT
     (ImageFormatProperties2 b)
     IO
     (Ptr (PhysicalDeviceImageFormatInfo2 a))
forall a b. (a -> b) -> a -> b
$ PhysicalDeviceImageFormatInfo2 a
-> (Ptr (PhysicalDeviceImageFormatInfo2 a)
    -> IO (ImageFormatProperties2 b))
-> IO (ImageFormatProperties2 b)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PhysicalDeviceImageFormatInfo2 a
imageFormatInfo)
  Ptr (ImageFormatProperties2 b)
pPImageFormatProperties <- ((Ptr (ImageFormatProperties2 b) -> IO (ImageFormatProperties2 b))
 -> IO (ImageFormatProperties2 b))
-> ContT
     (ImageFormatProperties2 b) IO (Ptr (ImageFormatProperties2 b))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct (ImageFormatProperties2 b) =>
(Ptr (ImageFormatProperties2 b) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(ImageFormatProperties2 _))
  Result
r <- IO Result -> ContT (ImageFormatProperties2 b) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (ImageFormatProperties2 b) IO Result)
-> IO Result -> ContT (ImageFormatProperties2 b) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pImageFormatInfo"
    ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2))
-> ("pImageFormatProperties"
    ::: Ptr (SomeStruct ImageFormatProperties2))
-> IO Result
vkGetPhysicalDeviceImageFormatProperties2' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) (Ptr (PhysicalDeviceImageFormatInfo2 a)
-> "pImageFormatInfo"
   ::: Ptr (SomeStruct PhysicalDeviceImageFormatInfo2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (PhysicalDeviceImageFormatInfo2 a)
pImageFormatInfo) (Ptr (ImageFormatProperties2 b)
-> "pImageFormatProperties"
   ::: Ptr (SomeStruct ImageFormatProperties2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (ImageFormatProperties2 b)
pPImageFormatProperties))
  IO () -> ContT (ImageFormatProperties2 b) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (ImageFormatProperties2 b) IO ())
-> IO () -> ContT (ImageFormatProperties2 b) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  ImageFormatProperties2 b
pImageFormatProperties <- IO (ImageFormatProperties2 b)
-> ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (ImageFormatProperties2 b)
 -> ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b))
-> IO (ImageFormatProperties2 b)
-> ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b)
forall a b. (a -> b) -> a -> b
$ Ptr (ImageFormatProperties2 b) -> IO (ImageFormatProperties2 b)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(ImageFormatProperties2 _) Ptr (ImageFormatProperties2 b)
pPImageFormatProperties
  ImageFormatProperties2 b
-> ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageFormatProperties2 b
 -> ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b))
-> ImageFormatProperties2 b
-> ContT (ImageFormatProperties2 b) IO (ImageFormatProperties2 b)
forall a b. (a -> b) -> a -> b
$ (ImageFormatProperties2 b
pImageFormatProperties)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceQueueFamilyProperties2
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr (SomeStruct QueueFamilyProperties2) -> IO ()) -> Ptr PhysicalDevice_T -> Ptr Word32 -> Ptr (SomeStruct QueueFamilyProperties2) -> IO ()

-- | vkGetPhysicalDeviceQueueFamilyProperties2 - Reports properties of the
-- queues of the specified physical device
--
-- = Description
--
-- 'getPhysicalDeviceQueueFamilyProperties2' behaves similarly to
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceQueueFamilyProperties',
-- with the ability to return extended information in a @pNext@ chain of
-- output structures.
--
-- == Valid Usage (Implicit)
--
-- -   @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   @pQueueFamilyPropertyCount@ /must/ be a valid pointer to a
--     @uint32_t@ value
--
-- -   If the value referenced by @pQueueFamilyPropertyCount@ is not @0@,
--     and @pQueueFamilyProperties@ is not @NULL@, @pQueueFamilyProperties@
--     /must/ be a valid pointer to an array of @pQueueFamilyPropertyCount@
--     'QueueFamilyProperties2' structures
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.PhysicalDevice', 'QueueFamilyProperties2'
getPhysicalDeviceQueueFamilyProperties2 :: forall a io
                                         . (Extendss QueueFamilyProperties2 a, PokeChain a, PeekChain a, MonadIO io)
                                        => -- | @physicalDevice@ is the handle to the physical device whose properties
                                           -- will be queried.
                                           PhysicalDevice
                                        -> io (("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
getPhysicalDeviceQueueFamilyProperties2 :: PhysicalDevice
-> io
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
getPhysicalDeviceQueueFamilyProperties2 physicalDevice :: PhysicalDevice
physicalDevice = IO ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
-> io
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
 -> io
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> (ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
    -> IO
         ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
-> io
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
  IO
  ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
-> IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
   IO
   ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
 -> io
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
-> io
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceQueueFamilyProperties2Ptr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties"
       ::: Ptr (SomeStruct QueueFamilyProperties2))
   -> IO ())
vkGetPhysicalDeviceQueueFamilyProperties2Ptr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
      -> ("pQueueFamilyProperties"
          ::: Ptr (SomeStruct QueueFamilyProperties2))
      -> IO ())
pVkGetPhysicalDeviceQueueFamilyProperties2 (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      ())
-> IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties"
       ::: Ptr (SomeStruct QueueFamilyProperties2))
   -> IO ())
vkGetPhysicalDeviceQueueFamilyProperties2Ptr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties"
       ::: Ptr (SomeStruct QueueFamilyProperties2))
   -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
      -> ("pQueueFamilyProperties"
          ::: Ptr (SomeStruct QueueFamilyProperties2))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties"
       ::: Ptr (SomeStruct QueueFamilyProperties2))
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceQueueFamilyProperties2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceQueueFamilyProperties2' :: Ptr PhysicalDevice_T
-> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> ("pQueueFamilyProperties"
    ::: Ptr (SomeStruct QueueFamilyProperties2))
-> IO ()
vkGetPhysicalDeviceQueueFamilyProperties2' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties"
       ::: Ptr (SomeStruct QueueFamilyProperties2))
   -> IO ())
-> Ptr PhysicalDevice_T
-> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> ("pQueueFamilyProperties"
    ::: Ptr (SomeStruct QueueFamilyProperties2))
-> IO ()
mkVkGetPhysicalDeviceQueueFamilyProperties2 FunPtr
  (Ptr PhysicalDevice_T
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pQueueFamilyProperties"
       ::: Ptr (SomeStruct QueueFamilyProperties2))
   -> IO ())
vkGetPhysicalDeviceQueueFamilyProperties2Ptr
  let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
  "pQueueFamilyPropertyCount" ::: Ptr Word32
pPQueueFamilyPropertyCount <- ((("pQueueFamilyPropertyCount" ::: Ptr Word32)
  -> IO
       ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
 -> IO
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ("pQueueFamilyPropertyCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> IO
        ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
  -> IO
       ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      ("pQueueFamilyPropertyCount" ::: Ptr Word32))
-> ((("pQueueFamilyPropertyCount" ::: Ptr Word32)
     -> IO
          ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
    -> IO
         ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ("pQueueFamilyPropertyCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> (("pQueueFamilyPropertyCount" ::: Ptr Word32) -> IO ())
-> (("pQueueFamilyPropertyCount" ::: Ptr Word32)
    -> IO
         ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pQueueFamilyPropertyCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pQueueFamilyPropertyCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      ())
-> IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> ("pQueueFamilyProperties"
    ::: Ptr (SomeStruct QueueFamilyProperties2))
-> IO ()
vkGetPhysicalDeviceQueueFamilyProperties2' Ptr PhysicalDevice_T
physicalDevice' ("pQueueFamilyPropertyCount" ::: Ptr Word32
pPQueueFamilyPropertyCount) (Ptr (QueueFamilyProperties2 Any)
-> "pQueueFamilyProperties"
   ::: Ptr (SomeStruct QueueFamilyProperties2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (QueueFamilyProperties2 Any)
forall a. Ptr a
nullPtr))
  Word32
pQueueFamilyPropertyCount <- IO Word32
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      Word32)
-> IO Word32
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     Word32
forall a b. (a -> b) -> a -> b
$ ("pQueueFamilyPropertyCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pQueueFamilyPropertyCount" ::: Ptr Word32
pPQueueFamilyPropertyCount
  Ptr (QueueFamilyProperties2 a)
pPQueueFamilyProperties <- ((Ptr (QueueFamilyProperties2 a)
  -> IO
       ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
 -> IO
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     (Ptr (QueueFamilyProperties2 a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (QueueFamilyProperties2 a)
   -> IO
        ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
  -> IO
       ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      (Ptr (QueueFamilyProperties2 a)))
-> ((Ptr (QueueFamilyProperties2 a)
     -> IO
          ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
    -> IO
         ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     (Ptr (QueueFamilyProperties2 a))
forall a b. (a -> b) -> a -> b
$ IO (Ptr (QueueFamilyProperties2 a))
-> (Ptr (QueueFamilyProperties2 a) -> IO ())
-> (Ptr (QueueFamilyProperties2 a)
    -> IO
         ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr (QueueFamilyProperties2 a))
forall a. Int -> IO (Ptr a)
callocBytes @(QueueFamilyProperties2 _) ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pQueueFamilyPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40)) Ptr (QueueFamilyProperties2 a) -> IO ()
forall a. Ptr a -> IO ()
free
  [()]
_ <- (Int
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      ())
-> [Int]
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     [()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((()
  -> IO
       ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
 -> IO
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
   -> IO
        ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
  -> IO
       ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      ())
-> ((()
     -> IO
          ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
    -> IO
         ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ()
forall a b. (a -> b) -> a -> b
$ Ptr (QueueFamilyProperties2 a)
-> IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
-> IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct (Ptr (QueueFamilyProperties2 a)
pPQueueFamilyProperties Ptr (QueueFamilyProperties2 a)
-> Int -> Ptr (QueueFamilyProperties2 a)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) :: Ptr (QueueFamilyProperties2 _)) (IO ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
 -> IO
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ((()
     -> IO
          ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
    -> IO
         ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> (()
    -> IO
         ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
 -> IO
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ()
-> IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pQueueFamilyPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
  IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      ())
-> IO ()
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> ("pQueueFamilyProperties"
    ::: Ptr (SomeStruct QueueFamilyProperties2))
-> IO ()
vkGetPhysicalDeviceQueueFamilyProperties2' Ptr PhysicalDevice_T
physicalDevice' ("pQueueFamilyPropertyCount" ::: Ptr Word32
pPQueueFamilyPropertyCount) (Ptr (QueueFamilyProperties2 a)
-> "pQueueFamilyProperties"
   ::: Ptr (SomeStruct QueueFamilyProperties2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (QueueFamilyProperties2 a)
pPQueueFamilyProperties)))
  Word32
pQueueFamilyPropertyCount' <- IO Word32
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      Word32)
-> IO Word32
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     Word32
forall a b. (a -> b) -> a -> b
$ ("pQueueFamilyPropertyCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pQueueFamilyPropertyCount" ::: Ptr Word32
pPQueueFamilyPropertyCount
  "queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)
pQueueFamilyProperties' <- IO ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO (QueueFamilyProperties2 a))
-> IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pQueueFamilyPropertyCount')) (\i :: Int
i -> Ptr (QueueFamilyProperties2 a) -> IO (QueueFamilyProperties2 a)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(QueueFamilyProperties2 _) (((Ptr (QueueFamilyProperties2 a)
pPQueueFamilyProperties) Ptr (QueueFamilyProperties2 a)
-> Int -> Ptr (QueueFamilyProperties2 a)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (QueueFamilyProperties2 _))))
  ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
 -> ContT
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
      IO
      ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)))
-> ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
-> ContT
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
     IO
     ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a))
forall a b. (a -> b) -> a -> b
$ ("queueFamilyProperties" ::: Vector (QueueFamilyProperties2 a)
pQueueFamilyProperties')


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceMemoryProperties2
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceMemoryProperties2) -> IO ()) -> Ptr PhysicalDevice_T -> Ptr (SomeStruct PhysicalDeviceMemoryProperties2) -> IO ()

-- | vkGetPhysicalDeviceMemoryProperties2 - Reports memory information for
-- the specified physical device
--
-- = Description
--
-- 'getPhysicalDeviceMemoryProperties2' behaves similarly to
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceMemoryProperties',
-- with the ability to return extended information in a @pNext@ chain of
-- output structures.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.PhysicalDevice',
-- 'PhysicalDeviceMemoryProperties2'
getPhysicalDeviceMemoryProperties2 :: forall a io
                                    . (Extendss PhysicalDeviceMemoryProperties2 a, PokeChain a, PeekChain a, MonadIO io)
                                   => -- | @physicalDevice@ is the handle to the device to query.
                                      --
                                      -- @physicalDevice@ /must/ be a valid
                                      -- 'Vulkan.Core10.Handles.PhysicalDevice' handle
                                      PhysicalDevice
                                   -> io (PhysicalDeviceMemoryProperties2 a)
getPhysicalDeviceMemoryProperties2 :: PhysicalDevice -> io (PhysicalDeviceMemoryProperties2 a)
getPhysicalDeviceMemoryProperties2 physicalDevice :: PhysicalDevice
physicalDevice = IO (PhysicalDeviceMemoryProperties2 a)
-> io (PhysicalDeviceMemoryProperties2 a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (PhysicalDeviceMemoryProperties2 a)
 -> io (PhysicalDeviceMemoryProperties2 a))
-> (ContT
      (PhysicalDeviceMemoryProperties2 a)
      IO
      (PhysicalDeviceMemoryProperties2 a)
    -> IO (PhysicalDeviceMemoryProperties2 a))
-> ContT
     (PhysicalDeviceMemoryProperties2 a)
     IO
     (PhysicalDeviceMemoryProperties2 a)
-> io (PhysicalDeviceMemoryProperties2 a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (PhysicalDeviceMemoryProperties2 a)
  IO
  (PhysicalDeviceMemoryProperties2 a)
-> IO (PhysicalDeviceMemoryProperties2 a)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (PhysicalDeviceMemoryProperties2 a)
   IO
   (PhysicalDeviceMemoryProperties2 a)
 -> io (PhysicalDeviceMemoryProperties2 a))
-> ContT
     (PhysicalDeviceMemoryProperties2 a)
     IO
     (PhysicalDeviceMemoryProperties2 a)
-> io (PhysicalDeviceMemoryProperties2 a)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceMemoryProperties2Ptr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties"
       ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
   -> IO ())
vkGetPhysicalDeviceMemoryProperties2Ptr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pMemoryProperties"
          ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
      -> IO ())
pVkGetPhysicalDeviceMemoryProperties2 (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO () -> ContT (PhysicalDeviceMemoryProperties2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (PhysicalDeviceMemoryProperties2 a) IO ())
-> IO () -> ContT (PhysicalDeviceMemoryProperties2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties"
       ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
   -> IO ())
vkGetPhysicalDeviceMemoryProperties2Ptr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties"
       ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
   -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pMemoryProperties"
          ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties"
       ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceMemoryProperties2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceMemoryProperties2' :: Ptr PhysicalDevice_T
-> ("pMemoryProperties"
    ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
-> IO ()
vkGetPhysicalDeviceMemoryProperties2' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties"
       ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
   -> IO ())
-> Ptr PhysicalDevice_T
-> ("pMemoryProperties"
    ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
-> IO ()
mkVkGetPhysicalDeviceMemoryProperties2 FunPtr
  (Ptr PhysicalDevice_T
   -> ("pMemoryProperties"
       ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
   -> IO ())
vkGetPhysicalDeviceMemoryProperties2Ptr
  Ptr (PhysicalDeviceMemoryProperties2 a)
pPMemoryProperties <- ((Ptr (PhysicalDeviceMemoryProperties2 a)
  -> IO (PhysicalDeviceMemoryProperties2 a))
 -> IO (PhysicalDeviceMemoryProperties2 a))
-> ContT
     (PhysicalDeviceMemoryProperties2 a)
     IO
     (Ptr (PhysicalDeviceMemoryProperties2 a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct (PhysicalDeviceMemoryProperties2 a) =>
(Ptr (PhysicalDeviceMemoryProperties2 a) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(PhysicalDeviceMemoryProperties2 _))
  IO () -> ContT (PhysicalDeviceMemoryProperties2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (PhysicalDeviceMemoryProperties2 a) IO ())
-> IO () -> ContT (PhysicalDeviceMemoryProperties2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pMemoryProperties"
    ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2))
-> IO ()
vkGetPhysicalDeviceMemoryProperties2' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) (Ptr (PhysicalDeviceMemoryProperties2 a)
-> "pMemoryProperties"
   ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PhysicalDeviceMemoryProperties2 a)
pPMemoryProperties))
  PhysicalDeviceMemoryProperties2 a
pMemoryProperties <- IO (PhysicalDeviceMemoryProperties2 a)
-> ContT
     (PhysicalDeviceMemoryProperties2 a)
     IO
     (PhysicalDeviceMemoryProperties2 a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (PhysicalDeviceMemoryProperties2 a)
 -> ContT
      (PhysicalDeviceMemoryProperties2 a)
      IO
      (PhysicalDeviceMemoryProperties2 a))
-> IO (PhysicalDeviceMemoryProperties2 a)
-> ContT
     (PhysicalDeviceMemoryProperties2 a)
     IO
     (PhysicalDeviceMemoryProperties2 a)
forall a b. (a -> b) -> a -> b
$ Ptr (PhysicalDeviceMemoryProperties2 a)
-> IO (PhysicalDeviceMemoryProperties2 a)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(PhysicalDeviceMemoryProperties2 _) Ptr (PhysicalDeviceMemoryProperties2 a)
pPMemoryProperties
  PhysicalDeviceMemoryProperties2 a
-> ContT
     (PhysicalDeviceMemoryProperties2 a)
     IO
     (PhysicalDeviceMemoryProperties2 a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMemoryProperties2 a
 -> ContT
      (PhysicalDeviceMemoryProperties2 a)
      IO
      (PhysicalDeviceMemoryProperties2 a))
-> PhysicalDeviceMemoryProperties2 a
-> ContT
     (PhysicalDeviceMemoryProperties2 a)
     IO
     (PhysicalDeviceMemoryProperties2 a)
forall a b. (a -> b) -> a -> b
$ (PhysicalDeviceMemoryProperties2 a
pMemoryProperties)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetPhysicalDeviceSparseImageFormatProperties2
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr PhysicalDeviceSparseImageFormatInfo2 -> Ptr Word32 -> Ptr SparseImageFormatProperties2 -> IO ()) -> Ptr PhysicalDevice_T -> Ptr PhysicalDeviceSparseImageFormatInfo2 -> Ptr Word32 -> Ptr SparseImageFormatProperties2 -> IO ()

-- | vkGetPhysicalDeviceSparseImageFormatProperties2 - Retrieve properties of
-- an image format applied to sparse images
--
-- = Description
--
-- 'getPhysicalDeviceSparseImageFormatProperties2' behaves identically to
-- 'Vulkan.Core10.SparseResourceMemoryManagement.getPhysicalDeviceSparseImageFormatProperties',
-- with the ability to return extended information by adding extending
-- structures to the @pNext@ chain of its @pProperties@ parameter.
--
-- == Valid Usage (Implicit)
--
-- -   @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   @pFormatInfo@ /must/ be a valid pointer to a valid
--     'PhysicalDeviceSparseImageFormatInfo2' structure
--
-- -   @pPropertyCount@ /must/ be a valid pointer to a @uint32_t@ value
--
-- -   If the value referenced by @pPropertyCount@ is not @0@, and
--     @pProperties@ is not @NULL@, @pProperties@ /must/ be a valid pointer
--     to an array of @pPropertyCount@ 'SparseImageFormatProperties2'
--     structures
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.PhysicalDevice',
-- 'PhysicalDeviceSparseImageFormatInfo2', 'SparseImageFormatProperties2'
getPhysicalDeviceSparseImageFormatProperties2 :: forall io
                                               . (MonadIO io)
                                              => -- | @physicalDevice@ is the physical device from which to query the sparse
                                                 -- image capabilities.
                                                 PhysicalDevice
                                              -> -- | @pFormatInfo@ is a pointer to a 'PhysicalDeviceSparseImageFormatInfo2'
                                                 -- structure containing input parameters to the command.
                                                 PhysicalDeviceSparseImageFormatInfo2
                                              -> io (("properties" ::: Vector SparseImageFormatProperties2))
getPhysicalDeviceSparseImageFormatProperties2 :: PhysicalDevice
-> PhysicalDeviceSparseImageFormatInfo2
-> io ("properties" ::: Vector SparseImageFormatProperties2)
getPhysicalDeviceSparseImageFormatProperties2 physicalDevice :: PhysicalDevice
physicalDevice formatInfo :: PhysicalDeviceSparseImageFormatInfo2
formatInfo = IO ("properties" ::: Vector SparseImageFormatProperties2)
-> io ("properties" ::: Vector SparseImageFormatProperties2)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("properties" ::: Vector SparseImageFormatProperties2)
 -> io ("properties" ::: Vector SparseImageFormatProperties2))
-> (ContT
      ("properties" ::: Vector SparseImageFormatProperties2)
      IO
      ("properties" ::: Vector SparseImageFormatProperties2)
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("properties" ::: Vector SparseImageFormatProperties2)
-> io ("properties" ::: Vector SparseImageFormatProperties2)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  ("properties" ::: Vector SparseImageFormatProperties2)
  IO
  ("properties" ::: Vector SparseImageFormatProperties2)
-> IO ("properties" ::: Vector SparseImageFormatProperties2)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   ("properties" ::: Vector SparseImageFormatProperties2)
   IO
   ("properties" ::: Vector SparseImageFormatProperties2)
 -> io ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("properties" ::: Vector SparseImageFormatProperties2)
-> io ("properties" ::: Vector SparseImageFormatProperties2)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPhysicalDeviceSparseImageFormatProperties2Ptr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
   -> IO ())
vkGetPhysicalDeviceSparseImageFormatProperties2Ptr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
      -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
      -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
      -> IO ())
pVkGetPhysicalDeviceSparseImageFormatProperties2 (PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice))
  IO ()
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2) IO ())
-> IO ()
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
   -> IO ())
vkGetPhysicalDeviceSparseImageFormatProperties2Ptr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
   -> IO ())
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
      -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
      -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkGetPhysicalDeviceSparseImageFormatProperties2 is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPhysicalDeviceSparseImageFormatProperties2' :: Ptr PhysicalDevice_T
-> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> IO ()
vkGetPhysicalDeviceSparseImageFormatProperties2' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
   -> IO ())
-> Ptr PhysicalDevice_T
-> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> IO ()
mkVkGetPhysicalDeviceSparseImageFormatProperties2 FunPtr
  (Ptr PhysicalDevice_T
   -> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
   -> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
   -> IO ())
vkGetPhysicalDeviceSparseImageFormatProperties2Ptr
  let physicalDevice' :: Ptr PhysicalDevice_T
physicalDevice' = PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)
  "pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
pFormatInfo <- ((("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
  -> IO ("properties" ::: Vector SparseImageFormatProperties2))
 -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
   -> IO ("properties" ::: Vector SparseImageFormatProperties2))
  -> IO ("properties" ::: Vector SparseImageFormatProperties2))
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2)
      IO
      ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2))
-> ((("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
     -> IO ("properties" ::: Vector SparseImageFormatProperties2))
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
forall a b. (a -> b) -> a -> b
$ PhysicalDeviceSparseImageFormatInfo2
-> (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> IO ("properties" ::: Vector SparseImageFormatProperties2)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PhysicalDeviceSparseImageFormatInfo2
formatInfo)
  "pQueueFamilyPropertyCount" ::: Ptr Word32
pPPropertyCount <- ((("pQueueFamilyPropertyCount" ::: Ptr Word32)
  -> IO ("properties" ::: Vector SparseImageFormatProperties2))
 -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("pQueueFamilyPropertyCount" ::: Ptr Word32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pQueueFamilyPropertyCount" ::: Ptr Word32)
   -> IO ("properties" ::: Vector SparseImageFormatProperties2))
  -> IO ("properties" ::: Vector SparseImageFormatProperties2))
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2)
      IO
      ("pQueueFamilyPropertyCount" ::: Ptr Word32))
-> ((("pQueueFamilyPropertyCount" ::: Ptr Word32)
     -> IO ("properties" ::: Vector SparseImageFormatProperties2))
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("pQueueFamilyPropertyCount" ::: Ptr Word32)
forall a b. (a -> b) -> a -> b
$ IO ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> (("pQueueFamilyPropertyCount" ::: Ptr Word32) -> IO ())
-> (("pQueueFamilyPropertyCount" ::: Ptr Word32)
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> IO ("properties" ::: Vector SparseImageFormatProperties2)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pQueueFamilyPropertyCount" ::: Ptr Word32)
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) ("pQueueFamilyPropertyCount" ::: Ptr Word32) -> IO ()
forall a. Ptr a -> IO ()
free
  IO ()
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2) IO ())
-> IO ()
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> IO ()
vkGetPhysicalDeviceSparseImageFormatProperties2' Ptr PhysicalDevice_T
physicalDevice' "pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
pFormatInfo ("pQueueFamilyPropertyCount" ::: Ptr Word32
pPPropertyCount) ("pProperties" ::: Ptr SparseImageFormatProperties2
forall a. Ptr a
nullPtr)
  Word32
pPropertyCount <- IO Word32
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2) IO Word32)
-> IO Word32
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pQueueFamilyPropertyCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pQueueFamilyPropertyCount" ::: Ptr Word32
pPPropertyCount
  "pProperties" ::: Ptr SparseImageFormatProperties2
pPProperties <- ((("pProperties" ::: Ptr SparseImageFormatProperties2)
  -> IO ("properties" ::: Vector SparseImageFormatProperties2))
 -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("pProperties" ::: Ptr SparseImageFormatProperties2)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pProperties" ::: Ptr SparseImageFormatProperties2)
   -> IO ("properties" ::: Vector SparseImageFormatProperties2))
  -> IO ("properties" ::: Vector SparseImageFormatProperties2))
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2)
      IO
      ("pProperties" ::: Ptr SparseImageFormatProperties2))
-> ((("pProperties" ::: Ptr SparseImageFormatProperties2)
     -> IO ("properties" ::: Vector SparseImageFormatProperties2))
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("pProperties" ::: Ptr SparseImageFormatProperties2)
forall a b. (a -> b) -> a -> b
$ IO ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> (("pProperties" ::: Ptr SparseImageFormatProperties2) -> IO ())
-> (("pProperties" ::: Ptr SparseImageFormatProperties2)
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> IO ("properties" ::: Vector SparseImageFormatProperties2)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pProperties" ::: Ptr SparseImageFormatProperties2)
forall a. Int -> IO (Ptr a)
callocBytes @SparseImageFormatProperties2 ((Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40)) ("pProperties" ::: Ptr SparseImageFormatProperties2) -> IO ()
forall a. Ptr a -> IO ()
free
  [()]
_ <- (Int
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2) IO ())
-> [Int]
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO [()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((() -> IO ("properties" ::: Vector SparseImageFormatProperties2))
 -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ("properties" ::: Vector SparseImageFormatProperties2))
  -> IO ("properties" ::: Vector SparseImageFormatProperties2))
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2) IO ())
-> ((()
     -> IO ("properties" ::: Vector SparseImageFormatProperties2))
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO ()
forall a b. (a -> b) -> a -> b
$ ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> IO ("properties" ::: Vector SparseImageFormatProperties2)
-> IO ("properties" ::: Vector SparseImageFormatProperties2)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct ("pProperties" ::: Ptr SparseImageFormatProperties2
pPProperties ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> Int -> "pProperties" ::: Ptr SparseImageFormatProperties2
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) :: Ptr SparseImageFormatProperties2) (IO ("properties" ::: Vector SparseImageFormatProperties2)
 -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> ((()
     -> IO ("properties" ::: Vector SparseImageFormatProperties2))
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> (()
    -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> IO ("properties" ::: Vector SparseImageFormatProperties2)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ("properties" ::: Vector SparseImageFormatProperties2))
-> () -> IO ("properties" ::: Vector SparseImageFormatProperties2)
forall a b. (a -> b) -> a -> b
$ ())) [0..(Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount)) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
  IO ()
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2) IO ())
-> IO ()
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> ("pQueueFamilyPropertyCount" ::: Ptr Word32)
-> ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> IO ()
vkGetPhysicalDeviceSparseImageFormatProperties2' Ptr PhysicalDevice_T
physicalDevice' "pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
pFormatInfo ("pQueueFamilyPropertyCount" ::: Ptr Word32
pPPropertyCount) (("pProperties" ::: Ptr SparseImageFormatProperties2
pPProperties))
  Word32
pPropertyCount' <- IO Word32
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO Word32
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Word32
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2) IO Word32)
-> IO Word32
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2) IO Word32
forall a b. (a -> b) -> a -> b
$ ("pQueueFamilyPropertyCount" ::: Ptr Word32) -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 "pQueueFamilyPropertyCount" ::: Ptr Word32
pPPropertyCount
  "properties" ::: Vector SparseImageFormatProperties2
pProperties' <- IO ("properties" ::: Vector SparseImageFormatProperties2)
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("properties" ::: Vector SparseImageFormatProperties2)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("properties" ::: Vector SparseImageFormatProperties2)
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2)
      IO
      ("properties" ::: Vector SparseImageFormatProperties2))
-> IO ("properties" ::: Vector SparseImageFormatProperties2)
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("properties" ::: Vector SparseImageFormatProperties2)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO SparseImageFormatProperties2)
-> IO ("properties" ::: Vector SparseImageFormatProperties2)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Word32 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32
pPropertyCount')) (\i :: Int
i -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> IO SparseImageFormatProperties2
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseImageFormatProperties2 ((("pProperties" ::: Ptr SparseImageFormatProperties2
pPProperties) ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> Int -> "pProperties" ::: Ptr SparseImageFormatProperties2
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr SparseImageFormatProperties2)))
  ("properties" ::: Vector SparseImageFormatProperties2)
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("properties" ::: Vector SparseImageFormatProperties2)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("properties" ::: Vector SparseImageFormatProperties2)
 -> ContT
      ("properties" ::: Vector SparseImageFormatProperties2)
      IO
      ("properties" ::: Vector SparseImageFormatProperties2))
-> ("properties" ::: Vector SparseImageFormatProperties2)
-> ContT
     ("properties" ::: Vector SparseImageFormatProperties2)
     IO
     ("properties" ::: Vector SparseImageFormatProperties2)
forall a b. (a -> b) -> a -> b
$ ("properties" ::: Vector SparseImageFormatProperties2
pProperties')


-- | VkPhysicalDeviceFeatures2 - Structure describing the fine-grained
-- features that can be supported by an implementation
--
-- = Members
--
-- The 'PhysicalDeviceFeatures2' structure is defined as:
--
-- = Description
--
-- The @pNext@ chain of this structure is used to extend the structure with
-- features defined by extensions. This structure /can/ be used in
-- 'getPhysicalDeviceFeatures2' or /can/ be included in the @pNext@ chain
-- of a 'Vulkan.Core10.Device.DeviceCreateInfo' structure, in which case it
-- controls which features are enabled in the device in lieu of
-- @pEnabledFeatures@.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceFeatures',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceFeatures2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2KHR'
data PhysicalDeviceFeatures2 (es :: [Type]) = PhysicalDeviceFeatures2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PhysicalDeviceFeatures2 es -> Chain es
next :: Chain es
  , -- | @features@ is a
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceFeatures' structure
    -- describing the fine-grained features of the Vulkan 1.0 API.
    PhysicalDeviceFeatures2 es -> PhysicalDeviceFeatures
features :: PhysicalDeviceFeatures
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceFeatures2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PhysicalDeviceFeatures2 es)

instance Extensible PhysicalDeviceFeatures2 where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_FEATURES_2
  setNext :: PhysicalDeviceFeatures2 ds
-> Chain es -> PhysicalDeviceFeatures2 es
setNext x :: PhysicalDeviceFeatures2 ds
x next :: Chain es
next = PhysicalDeviceFeatures2 ds
x{$sel:next:PhysicalDeviceFeatures2 :: Chain es
next = Chain es
next}
  getNext :: PhysicalDeviceFeatures2 es -> Chain es
getNext PhysicalDeviceFeatures2{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends PhysicalDeviceFeatures2 e => b) -> Maybe b
  extends :: proxy e -> (Extends PhysicalDeviceFeatures2 e => b) -> Maybe b
extends _ f :: Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceShaderTerminateInvocationFeaturesKHR) =>
Maybe (e :~: PhysicalDeviceShaderTerminateInvocationFeaturesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderTerminateInvocationFeaturesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceFragmentShadingRateFeaturesKHR) =>
Maybe (e :~: PhysicalDeviceFragmentShadingRateFeaturesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceFragmentShadingRateFeaturesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceShaderImageAtomicInt64FeaturesEXT) =>
Maybe (e :~: PhysicalDeviceShaderImageAtomicInt64FeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderImageAtomicInt64FeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDevice4444FormatsFeaturesEXT) =>
Maybe (e :~: PhysicalDevice4444FormatsFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevice4444FormatsFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDevicePortabilitySubsetFeaturesKHR) =>
Maybe (e :~: PhysicalDevicePortabilitySubsetFeaturesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePortabilitySubsetFeaturesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceImageRobustnessFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceImageRobustnessFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceImageRobustnessFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceRobustness2FeaturesEXT) =>
Maybe (e :~: PhysicalDeviceRobustness2FeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceRobustness2FeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceDiagnosticsConfigFeaturesNV) =>
Maybe (e :~: PhysicalDeviceDiagnosticsConfigFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDiagnosticsConfigFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceExtendedDynamicStateFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceExtendedDynamicStateFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceExtendedDynamicStateFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceCustomBorderColorFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceCustomBorderColorFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceCustomBorderColorFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceCoherentMemoryFeaturesAMD) =>
Maybe (e :~: PhysicalDeviceCoherentMemoryFeaturesAMD)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceCoherentMemoryFeaturesAMD = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceVulkan12Features) =>
Maybe (e :~: PhysicalDeviceVulkan12Features)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceVulkan12Features = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceVulkan11Features) =>
Maybe (e :~: PhysicalDeviceVulkan11Features)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceVulkan11Features = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDevicePipelineCreationCacheControlFeaturesEXT) =>
Maybe (e :~: PhysicalDevicePipelineCreationCacheControlFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePipelineCreationCacheControlFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceLineRasterizationFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceLineRasterizationFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceLineRasterizationFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceSubgroupSizeControlFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceSubgroupSizeControlFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceSubgroupSizeControlFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceTexelBufferAlignmentFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceTexelBufferAlignmentFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceTexelBufferAlignmentFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable
   PhysicalDeviceShaderDemoteToHelperInvocationFeaturesEXT) =>
Maybe
  (e :~: PhysicalDeviceShaderDemoteToHelperInvocationFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderDemoteToHelperInvocationFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDevicePipelineExecutablePropertiesFeaturesKHR) =>
Maybe (e :~: PhysicalDevicePipelineExecutablePropertiesFeaturesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePipelineExecutablePropertiesFeaturesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceSeparateDepthStencilLayoutsFeatures) =>
Maybe (e :~: PhysicalDeviceSeparateDepthStencilLayoutsFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceSeparateDepthStencilLayoutsFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceFragmentShaderInterlockFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceFragmentShaderInterlockFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceFragmentShaderInterlockFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceShaderSMBuiltinsFeaturesNV) =>
Maybe (e :~: PhysicalDeviceShaderSMBuiltinsFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderSMBuiltinsFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceIndexTypeUint8FeaturesEXT) =>
Maybe (e :~: PhysicalDeviceIndexTypeUint8FeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceIndexTypeUint8FeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceShaderClockFeaturesKHR) =>
Maybe (e :~: PhysicalDeviceShaderClockFeaturesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderClockFeaturesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceShaderIntegerFunctions2FeaturesINTEL) =>
Maybe (e :~: PhysicalDeviceShaderIntegerFunctions2FeaturesINTEL)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderIntegerFunctions2FeaturesINTEL = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceCoverageReductionModeFeaturesNV) =>
Maybe (e :~: PhysicalDeviceCoverageReductionModeFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceCoverageReductionModeFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDevicePerformanceQueryFeaturesKHR) =>
Maybe (e :~: PhysicalDevicePerformanceQueryFeaturesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePerformanceQueryFeaturesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceYcbcrImageArraysFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceYcbcrImageArraysFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceYcbcrImageArraysFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceCooperativeMatrixFeaturesNV) =>
Maybe (e :~: PhysicalDeviceCooperativeMatrixFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceCooperativeMatrixFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceTextureCompressionASTCHDRFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceTextureCompressionASTCHDRFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceTextureCompressionASTCHDRFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceImagelessFramebufferFeatures) =>
Maybe (e :~: PhysicalDeviceImagelessFramebufferFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceImagelessFramebufferFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceBufferDeviceAddressFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceBufferDeviceAddressFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceBufferDeviceAddressFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceBufferDeviceAddressFeatures) =>
Maybe (e :~: PhysicalDeviceBufferDeviceAddressFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceBufferDeviceAddressFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceMemoryPriorityFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceMemoryPriorityFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceMemoryPriorityFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceDepthClipEnableFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceDepthClipEnableFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDepthClipEnableFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceUniformBufferStandardLayoutFeatures) =>
Maybe (e :~: PhysicalDeviceUniformBufferStandardLayoutFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceUniformBufferStandardLayoutFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceScalarBlockLayoutFeatures) =>
Maybe (e :~: PhysicalDeviceScalarBlockLayoutFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceScalarBlockLayoutFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceFragmentDensityMap2FeaturesEXT) =>
Maybe (e :~: PhysicalDeviceFragmentDensityMap2FeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceFragmentDensityMap2FeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceFragmentDensityMapFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceFragmentDensityMapFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceFragmentDensityMapFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceRayTracingFeaturesKHR) =>
Maybe (e :~: PhysicalDeviceRayTracingFeaturesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceRayTracingFeaturesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceMeshShaderFeaturesNV) =>
Maybe (e :~: PhysicalDeviceMeshShaderFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceMeshShaderFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceShadingRateImageFeaturesNV) =>
Maybe (e :~: PhysicalDeviceShadingRateImageFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShadingRateImageFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable
   PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV) =>
Maybe
  (e :~: PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceShaderImageFootprintFeaturesNV) =>
Maybe (e :~: PhysicalDeviceShaderImageFootprintFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderImageFootprintFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceFragmentShaderBarycentricFeaturesNV) =>
Maybe (e :~: PhysicalDeviceFragmentShaderBarycentricFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceFragmentShaderBarycentricFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceComputeShaderDerivativesFeaturesNV) =>
Maybe (e :~: PhysicalDeviceComputeShaderDerivativesFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceComputeShaderDerivativesFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceCornerSampledImageFeaturesNV) =>
Maybe (e :~: PhysicalDeviceCornerSampledImageFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceCornerSampledImageFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceExclusiveScissorFeaturesNV) =>
Maybe (e :~: PhysicalDeviceExclusiveScissorFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceExclusiveScissorFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceRepresentativeFragmentTestFeaturesNV) =>
Maybe (e :~: PhysicalDeviceRepresentativeFragmentTestFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceRepresentativeFragmentTestFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceTransformFeedbackFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceTransformFeedbackFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceTransformFeedbackFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceASTCDecodeFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceASTCDecodeFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceASTCDecodeFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceVertexAttributeDivisorFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceVertexAttributeDivisorFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceVertexAttributeDivisorFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceShaderAtomicFloatFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceShaderAtomicFloatFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderAtomicFloatFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceShaderAtomicInt64Features) =>
Maybe (e :~: PhysicalDeviceShaderAtomicInt64Features)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderAtomicInt64Features = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceVulkanMemoryModelFeatures) =>
Maybe (e :~: PhysicalDeviceVulkanMemoryModelFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceVulkanMemoryModelFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceConditionalRenderingFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceConditionalRenderingFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceConditionalRenderingFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDevice8BitStorageFeatures) =>
Maybe (e :~: PhysicalDevice8BitStorageFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevice8BitStorageFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceTimelineSemaphoreFeatures) =>
Maybe (e :~: PhysicalDeviceTimelineSemaphoreFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceTimelineSemaphoreFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceDescriptorIndexingFeatures) =>
Maybe (e :~: PhysicalDeviceDescriptorIndexingFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDescriptorIndexingFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceDeviceMemoryReportFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceDeviceMemoryReportFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDeviceMemoryReportFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceHostQueryResetFeatures) =>
Maybe (e :~: PhysicalDeviceHostQueryResetFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceHostQueryResetFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceShaderFloat16Int8Features) =>
Maybe (e :~: PhysicalDeviceShaderFloat16Int8Features)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderFloat16Int8Features = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceShaderDrawParametersFeatures) =>
Maybe (e :~: PhysicalDeviceShaderDrawParametersFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderDrawParametersFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceInlineUniformBlockFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceInlineUniformBlockFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceInlineUniformBlockFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceBlendOperationAdvancedFeaturesEXT) =>
Maybe (e :~: PhysicalDeviceBlendOperationAdvancedFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceBlendOperationAdvancedFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceProtectedMemoryFeatures) =>
Maybe (e :~: PhysicalDeviceProtectedMemoryFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceProtectedMemoryFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceSamplerYcbcrConversionFeatures) =>
Maybe (e :~: PhysicalDeviceSamplerYcbcrConversionFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceSamplerYcbcrConversionFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceShaderSubgroupExtendedTypesFeatures) =>
Maybe (e :~: PhysicalDeviceShaderSubgroupExtendedTypesFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderSubgroupExtendedTypesFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDevice16BitStorageFeatures) =>
Maybe (e :~: PhysicalDevice16BitStorageFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevice16BitStorageFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceMultiviewFeatures) =>
Maybe (e :~: PhysicalDeviceMultiviewFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceMultiviewFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceVariablePointersFeatures) =>
Maybe (e :~: PhysicalDeviceVariablePointersFeatures)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceVariablePointersFeatures = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDevicePrivateDataFeaturesEXT) =>
Maybe (e :~: PhysicalDevicePrivateDataFeaturesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePrivateDataFeaturesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceDeviceGeneratedCommandsFeaturesNV) =>
Maybe (e :~: PhysicalDeviceDeviceGeneratedCommandsFeaturesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDeviceGeneratedCommandsFeaturesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceFeatures2 e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss PhysicalDeviceFeatures2 es, PokeChain es) => ToCStruct (PhysicalDeviceFeatures2 es) where
  withCStruct :: PhysicalDeviceFeatures2 es
-> (Ptr (PhysicalDeviceFeatures2 es) -> IO b) -> IO b
withCStruct x :: PhysicalDeviceFeatures2 es
x f :: Ptr (PhysicalDeviceFeatures2 es) -> IO b
f = Int -> Int -> (Ptr (PhysicalDeviceFeatures2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 240 8 ((Ptr (PhysicalDeviceFeatures2 es) -> IO b) -> IO b)
-> (Ptr (PhysicalDeviceFeatures2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PhysicalDeviceFeatures2 es)
p -> Ptr (PhysicalDeviceFeatures2 es)
-> PhysicalDeviceFeatures2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PhysicalDeviceFeatures2 es)
p PhysicalDeviceFeatures2 es
x (Ptr (PhysicalDeviceFeatures2 es) -> IO b
f Ptr (PhysicalDeviceFeatures2 es)
p)
  pokeCStruct :: Ptr (PhysicalDeviceFeatures2 es)
-> PhysicalDeviceFeatures2 es -> IO b -> IO b
pokeCStruct p :: Ptr (PhysicalDeviceFeatures2 es)
p PhysicalDeviceFeatures2{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceFeatures2 es)
p Ptr (PhysicalDeviceFeatures2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_FEATURES_2)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceFeatures2 es)
p Ptr (PhysicalDeviceFeatures2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDeviceFeatures
-> PhysicalDeviceFeatures -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (PhysicalDeviceFeatures2 es)
p Ptr (PhysicalDeviceFeatures2 es)
-> Int -> Ptr PhysicalDeviceFeatures
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceFeatures)) (PhysicalDeviceFeatures
features) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 240
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PhysicalDeviceFeatures2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PhysicalDeviceFeatures2 es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceFeatures2 es)
p Ptr (PhysicalDeviceFeatures2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_FEATURES_2)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceFeatures2 es)
p Ptr (PhysicalDeviceFeatures2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDeviceFeatures
-> PhysicalDeviceFeatures -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (PhysicalDeviceFeatures2 es)
p Ptr (PhysicalDeviceFeatures2 es)
-> Int -> Ptr PhysicalDeviceFeatures
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceFeatures)) (PhysicalDeviceFeatures
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PhysicalDeviceFeatures2 es, PeekChain es) => FromCStruct (PhysicalDeviceFeatures2 es) where
  peekCStruct :: Ptr (PhysicalDeviceFeatures2 es) -> IO (PhysicalDeviceFeatures2 es)
peekCStruct p :: Ptr (PhysicalDeviceFeatures2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PhysicalDeviceFeatures2 es)
p Ptr (PhysicalDeviceFeatures2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PhysicalDeviceFeatures
features <- Ptr PhysicalDeviceFeatures -> IO PhysicalDeviceFeatures
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PhysicalDeviceFeatures ((Ptr (PhysicalDeviceFeatures2 es)
p Ptr (PhysicalDeviceFeatures2 es)
-> Int -> Ptr PhysicalDeviceFeatures
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceFeatures))
    PhysicalDeviceFeatures2 es -> IO (PhysicalDeviceFeatures2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceFeatures2 es -> IO (PhysicalDeviceFeatures2 es))
-> PhysicalDeviceFeatures2 es -> IO (PhysicalDeviceFeatures2 es)
forall a b. (a -> b) -> a -> b
$ Chain es -> PhysicalDeviceFeatures -> PhysicalDeviceFeatures2 es
forall (es :: [*]).
Chain es -> PhysicalDeviceFeatures -> PhysicalDeviceFeatures2 es
PhysicalDeviceFeatures2
             Chain es
next PhysicalDeviceFeatures
features

instance es ~ '[] => Zero (PhysicalDeviceFeatures2 es) where
  zero :: PhysicalDeviceFeatures2 es
zero = Chain es -> PhysicalDeviceFeatures -> PhysicalDeviceFeatures2 es
forall (es :: [*]).
Chain es -> PhysicalDeviceFeatures -> PhysicalDeviceFeatures2 es
PhysicalDeviceFeatures2
           ()
           PhysicalDeviceFeatures
forall a. Zero a => a
zero


-- | VkPhysicalDeviceProperties2 - Structure specifying physical device
-- properties
--
-- = Description
--
-- The @pNext@ chain of this structure is used to extend the structure with
-- properties defined by extensions.
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_PROPERTIES_2'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PhysicalDeviceBlendOperationAdvancedPropertiesEXT',
--     'Vulkan.Extensions.VK_EXT_conservative_rasterization.PhysicalDeviceConservativeRasterizationPropertiesEXT',
--     'Vulkan.Extensions.VK_NV_cooperative_matrix.PhysicalDeviceCooperativeMatrixPropertiesNV',
--     'Vulkan.Extensions.VK_EXT_custom_border_color.PhysicalDeviceCustomBorderColorPropertiesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_depth_stencil_resolve.PhysicalDeviceDepthStencilResolveProperties',
--     'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingProperties',
--     'Vulkan.Extensions.VK_NV_device_generated_commands.PhysicalDeviceDeviceGeneratedCommandsPropertiesNV',
--     'Vulkan.Extensions.VK_EXT_discard_rectangles.PhysicalDeviceDiscardRectanglePropertiesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_driver_properties.PhysicalDeviceDriverProperties',
--     'Vulkan.Extensions.VK_EXT_external_memory_host.PhysicalDeviceExternalMemoryHostPropertiesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_shader_float_controls.PhysicalDeviceFloatControlsProperties',
--     'Vulkan.Extensions.VK_EXT_fragment_density_map2.PhysicalDeviceFragmentDensityMap2PropertiesEXT',
--     'Vulkan.Extensions.VK_EXT_fragment_density_map.PhysicalDeviceFragmentDensityMapPropertiesEXT',
--     'Vulkan.Extensions.VK_KHR_fragment_shading_rate.PhysicalDeviceFragmentShadingRatePropertiesKHR',
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.PhysicalDeviceIDProperties',
--     'Vulkan.Extensions.VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockPropertiesEXT',
--     'Vulkan.Extensions.VK_EXT_line_rasterization.PhysicalDeviceLineRasterizationPropertiesEXT',
--     'Vulkan.Core11.Promoted_From_VK_KHR_maintenance3.PhysicalDeviceMaintenance3Properties',
--     'Vulkan.Extensions.VK_NV_mesh_shader.PhysicalDeviceMeshShaderPropertiesNV',
--     'Vulkan.Extensions.VK_NVX_multiview_per_view_attributes.PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX',
--     'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewProperties',
--     'Vulkan.Extensions.VK_EXT_pci_bus_info.PhysicalDevicePCIBusInfoPropertiesEXT',
--     'Vulkan.Extensions.VK_KHR_performance_query.PhysicalDevicePerformanceQueryPropertiesKHR',
--     'Vulkan.Core11.Promoted_From_VK_KHR_maintenance2.PhysicalDevicePointClippingProperties',
--     'Vulkan.Extensions.VK_KHR_portability_subset.PhysicalDevicePortabilitySubsetPropertiesKHR',
--     'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.PhysicalDeviceProtectedMemoryProperties',
--     'Vulkan.Extensions.VK_KHR_push_descriptor.PhysicalDevicePushDescriptorPropertiesKHR',
--     'Vulkan.Extensions.VK_KHR_ray_tracing.PhysicalDeviceRayTracingPropertiesKHR',
--     'Vulkan.Extensions.VK_NV_ray_tracing.PhysicalDeviceRayTracingPropertiesNV',
--     'Vulkan.Extensions.VK_EXT_robustness2.PhysicalDeviceRobustness2PropertiesEXT',
--     'Vulkan.Extensions.VK_EXT_sample_locations.PhysicalDeviceSampleLocationsPropertiesEXT',
--     'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.PhysicalDeviceSamplerFilterMinmaxProperties',
--     'Vulkan.Extensions.VK_AMD_shader_core_properties2.PhysicalDeviceShaderCoreProperties2AMD',
--     'Vulkan.Extensions.VK_AMD_shader_core_properties.PhysicalDeviceShaderCorePropertiesAMD',
--     'Vulkan.Extensions.VK_NV_shader_sm_builtins.PhysicalDeviceShaderSMBuiltinsPropertiesNV',
--     'Vulkan.Extensions.VK_NV_shading_rate_image.PhysicalDeviceShadingRateImagePropertiesNV',
--     'Vulkan.Core11.Originally_Based_On_VK_KHR_subgroup.PhysicalDeviceSubgroupProperties',
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PhysicalDeviceSubgroupSizeControlPropertiesEXT',
--     'Vulkan.Extensions.VK_EXT_texel_buffer_alignment.PhysicalDeviceTexelBufferAlignmentPropertiesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.PhysicalDeviceTimelineSemaphoreProperties',
--     'Vulkan.Extensions.VK_EXT_transform_feedback.PhysicalDeviceTransformFeedbackPropertiesEXT',
--     'Vulkan.Extensions.VK_EXT_vertex_attribute_divisor.PhysicalDeviceVertexAttributeDivisorPropertiesEXT',
--     'Vulkan.Core12.PhysicalDeviceVulkan11Properties', or
--     'Vulkan.Core12.PhysicalDeviceVulkan12Properties'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- = See Also
--
-- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceProperties',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2KHR'
data PhysicalDeviceProperties2 (es :: [Type]) = PhysicalDeviceProperties2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PhysicalDeviceProperties2 es -> Chain es
next :: Chain es
  , -- | @properties@ is a
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceProperties' structure
    -- describing properties of the physical device. This structure is written
    -- with the same values as if it were written by
    -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceProperties'.
    PhysicalDeviceProperties2 es -> PhysicalDeviceProperties
properties :: PhysicalDeviceProperties
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceProperties2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PhysicalDeviceProperties2 es)

instance Extensible PhysicalDeviceProperties2 where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PROPERTIES_2
  setNext :: PhysicalDeviceProperties2 ds
-> Chain es -> PhysicalDeviceProperties2 es
setNext x :: PhysicalDeviceProperties2 ds
x next :: Chain es
next = PhysicalDeviceProperties2 ds
x{$sel:next:PhysicalDeviceProperties2 :: Chain es
next = Chain es
next}
  getNext :: PhysicalDeviceProperties2 es -> Chain es
getNext PhysicalDeviceProperties2{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends PhysicalDeviceProperties2 e => b) -> Maybe b
  extends :: proxy e -> (Extends PhysicalDeviceProperties2 e => b) -> Maybe b
extends _ f :: Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceFragmentShadingRatePropertiesKHR) =>
Maybe (e :~: PhysicalDeviceFragmentShadingRatePropertiesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceFragmentShadingRatePropertiesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDevicePortabilitySubsetPropertiesKHR) =>
Maybe (e :~: PhysicalDevicePortabilitySubsetPropertiesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePortabilitySubsetPropertiesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceRobustness2PropertiesEXT) =>
Maybe (e :~: PhysicalDeviceRobustness2PropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceRobustness2PropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceCustomBorderColorPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceCustomBorderColorPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceCustomBorderColorPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceVulkan12Properties) =>
Maybe (e :~: PhysicalDeviceVulkan12Properties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceVulkan12Properties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceVulkan11Properties) =>
Maybe (e :~: PhysicalDeviceVulkan11Properties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceVulkan11Properties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceLineRasterizationPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceLineRasterizationPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceLineRasterizationPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceSubgroupSizeControlPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceSubgroupSizeControlPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceSubgroupSizeControlPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceTexelBufferAlignmentPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceTexelBufferAlignmentPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceTexelBufferAlignmentPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceShaderSMBuiltinsPropertiesNV) =>
Maybe (e :~: PhysicalDeviceShaderSMBuiltinsPropertiesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderSMBuiltinsPropertiesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDevicePerformanceQueryPropertiesKHR) =>
Maybe (e :~: PhysicalDevicePerformanceQueryPropertiesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePerformanceQueryPropertiesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceCooperativeMatrixPropertiesNV) =>
Maybe (e :~: PhysicalDeviceCooperativeMatrixPropertiesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceCooperativeMatrixPropertiesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceFragmentDensityMap2PropertiesEXT) =>
Maybe (e :~: PhysicalDeviceFragmentDensityMap2PropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceFragmentDensityMap2PropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceFragmentDensityMapPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceFragmentDensityMapPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceFragmentDensityMapPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceRayTracingPropertiesNV) =>
Maybe (e :~: PhysicalDeviceRayTracingPropertiesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceRayTracingPropertiesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceRayTracingPropertiesKHR) =>
Maybe (e :~: PhysicalDeviceRayTracingPropertiesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceRayTracingPropertiesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceMeshShaderPropertiesNV) =>
Maybe (e :~: PhysicalDeviceMeshShaderPropertiesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceMeshShaderPropertiesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceShadingRateImagePropertiesNV) =>
Maybe (e :~: PhysicalDeviceShadingRateImagePropertiesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShadingRateImagePropertiesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceTransformFeedbackPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceTransformFeedbackPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceTransformFeedbackPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceDepthStencilResolveProperties) =>
Maybe (e :~: PhysicalDeviceDepthStencilResolveProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDepthStencilResolveProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDevicePCIBusInfoPropertiesEXT) =>
Maybe (e :~: PhysicalDevicePCIBusInfoPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePCIBusInfoPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceVertexAttributeDivisorPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceVertexAttributeDivisorPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceVertexAttributeDivisorPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceTimelineSemaphoreProperties) =>
Maybe (e :~: PhysicalDeviceTimelineSemaphoreProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceTimelineSemaphoreProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceDescriptorIndexingProperties) =>
Maybe (e :~: PhysicalDeviceDescriptorIndexingProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDescriptorIndexingProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceShaderCoreProperties2AMD) =>
Maybe (e :~: PhysicalDeviceShaderCoreProperties2AMD)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderCoreProperties2AMD = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceShaderCorePropertiesAMD) =>
Maybe (e :~: PhysicalDeviceShaderCorePropertiesAMD)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceShaderCorePropertiesAMD = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceConservativeRasterizationPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceConservativeRasterizationPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceConservativeRasterizationPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceExternalMemoryHostPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceExternalMemoryHostPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceExternalMemoryHostPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceFloatControlsProperties) =>
Maybe (e :~: PhysicalDeviceFloatControlsProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceFloatControlsProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceMaintenance3Properties) =>
Maybe (e :~: PhysicalDeviceMaintenance3Properties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceMaintenance3Properties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceInlineUniformBlockPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceInlineUniformBlockPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceInlineUniformBlockPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceBlendOperationAdvancedPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceBlendOperationAdvancedPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceBlendOperationAdvancedPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceSampleLocationsPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceSampleLocationsPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceSampleLocationsPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceSamplerFilterMinmaxProperties) =>
Maybe (e :~: PhysicalDeviceSamplerFilterMinmaxProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceSamplerFilterMinmaxProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceProtectedMemoryProperties) =>
Maybe (e :~: PhysicalDeviceProtectedMemoryProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceProtectedMemoryProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDevicePointClippingProperties) =>
Maybe (e :~: PhysicalDevicePointClippingProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePointClippingProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceSubgroupProperties) =>
Maybe (e :~: PhysicalDeviceSubgroupProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceSubgroupProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX) =>
Maybe (e :~: PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceMultiviewPerViewAttributesPropertiesNVX = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceDiscardRectanglePropertiesEXT) =>
Maybe (e :~: PhysicalDeviceDiscardRectanglePropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDiscardRectanglePropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceMultiviewProperties) =>
Maybe (e :~: PhysicalDeviceMultiviewProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceMultiviewProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceIDProperties) =>
Maybe (e :~: PhysicalDeviceIDProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceIDProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceDriverProperties) =>
Maybe (e :~: PhysicalDeviceDriverProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDriverProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDevicePushDescriptorPropertiesKHR) =>
Maybe (e :~: PhysicalDevicePushDescriptorPropertiesKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDevicePushDescriptorPropertiesKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceDeviceGeneratedCommandsPropertiesNV) =>
Maybe (e :~: PhysicalDeviceDeviceGeneratedCommandsPropertiesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceDeviceGeneratedCommandsPropertiesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceProperties2 e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss PhysicalDeviceProperties2 es, PokeChain es) => ToCStruct (PhysicalDeviceProperties2 es) where
  withCStruct :: PhysicalDeviceProperties2 es
-> (Ptr (PhysicalDeviceProperties2 es) -> IO b) -> IO b
withCStruct x :: PhysicalDeviceProperties2 es
x f :: Ptr (PhysicalDeviceProperties2 es) -> IO b
f = Int -> Int -> (Ptr (PhysicalDeviceProperties2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 840 8 ((Ptr (PhysicalDeviceProperties2 es) -> IO b) -> IO b)
-> (Ptr (PhysicalDeviceProperties2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PhysicalDeviceProperties2 es)
p -> Ptr (PhysicalDeviceProperties2 es)
-> PhysicalDeviceProperties2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PhysicalDeviceProperties2 es)
p PhysicalDeviceProperties2 es
x (Ptr (PhysicalDeviceProperties2 es) -> IO b
f Ptr (PhysicalDeviceProperties2 es)
p)
  pokeCStruct :: Ptr (PhysicalDeviceProperties2 es)
-> PhysicalDeviceProperties2 es -> IO b -> IO b
pokeCStruct p :: Ptr (PhysicalDeviceProperties2 es)
p PhysicalDeviceProperties2{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceProperties2 es)
p Ptr (PhysicalDeviceProperties2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PROPERTIES_2)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceProperties2 es)
p Ptr (PhysicalDeviceProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDeviceProperties
-> PhysicalDeviceProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (PhysicalDeviceProperties2 es)
p Ptr (PhysicalDeviceProperties2 es)
-> Int -> Ptr PhysicalDeviceProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceProperties)) (PhysicalDeviceProperties
properties) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 840
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PhysicalDeviceProperties2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PhysicalDeviceProperties2 es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceProperties2 es)
p Ptr (PhysicalDeviceProperties2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_PROPERTIES_2)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceProperties2 es)
p Ptr (PhysicalDeviceProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDeviceProperties
-> PhysicalDeviceProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (PhysicalDeviceProperties2 es)
p Ptr (PhysicalDeviceProperties2 es)
-> Int -> Ptr PhysicalDeviceProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceProperties)) (PhysicalDeviceProperties
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PhysicalDeviceProperties2 es, PeekChain es) => FromCStruct (PhysicalDeviceProperties2 es) where
  peekCStruct :: Ptr (PhysicalDeviceProperties2 es)
-> IO (PhysicalDeviceProperties2 es)
peekCStruct p :: Ptr (PhysicalDeviceProperties2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PhysicalDeviceProperties2 es)
p Ptr (PhysicalDeviceProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PhysicalDeviceProperties
properties <- Ptr PhysicalDeviceProperties -> IO PhysicalDeviceProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PhysicalDeviceProperties ((Ptr (PhysicalDeviceProperties2 es)
p Ptr (PhysicalDeviceProperties2 es)
-> Int -> Ptr PhysicalDeviceProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceProperties))
    PhysicalDeviceProperties2 es -> IO (PhysicalDeviceProperties2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceProperties2 es -> IO (PhysicalDeviceProperties2 es))
-> PhysicalDeviceProperties2 es
-> IO (PhysicalDeviceProperties2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PhysicalDeviceProperties -> PhysicalDeviceProperties2 es
forall (es :: [*]).
Chain es
-> PhysicalDeviceProperties -> PhysicalDeviceProperties2 es
PhysicalDeviceProperties2
             Chain es
next PhysicalDeviceProperties
properties

instance es ~ '[] => Zero (PhysicalDeviceProperties2 es) where
  zero :: PhysicalDeviceProperties2 es
zero = Chain es
-> PhysicalDeviceProperties -> PhysicalDeviceProperties2 es
forall (es :: [*]).
Chain es
-> PhysicalDeviceProperties -> PhysicalDeviceProperties2 es
PhysicalDeviceProperties2
           ()
           PhysicalDeviceProperties
forall a. Zero a => a
zero


-- | VkFormatProperties2 - Structure specifying image format properties
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_FORMAT_PROPERTIES_2'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_image_drm_format_modifier.DrmFormatModifierPropertiesListEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- = See Also
--
-- 'Vulkan.Core10.DeviceInitialization.FormatProperties',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceFormatProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceFormatProperties2KHR'
data FormatProperties2 (es :: [Type]) = FormatProperties2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    FormatProperties2 es -> Chain es
next :: Chain es
  , -- | @formatProperties@ is a
    -- 'Vulkan.Core10.DeviceInitialization.FormatProperties' structure
    -- describing features supported by the requested format.
    FormatProperties2 es -> FormatProperties
formatProperties :: FormatProperties
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (FormatProperties2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (FormatProperties2 es)

instance Extensible FormatProperties2 where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_FORMAT_PROPERTIES_2
  setNext :: FormatProperties2 ds -> Chain es -> FormatProperties2 es
setNext x :: FormatProperties2 ds
x next :: Chain es
next = FormatProperties2 ds
x{$sel:next:FormatProperties2 :: Chain es
next = Chain es
next}
  getNext :: FormatProperties2 es -> Chain es
getNext FormatProperties2{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends FormatProperties2 e => b) -> Maybe b
  extends :: proxy e -> (Extends FormatProperties2 e => b) -> Maybe b
extends _ f :: Extends FormatProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable DrmFormatModifierPropertiesListEXT) =>
Maybe (e :~: DrmFormatModifierPropertiesListEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DrmFormatModifierPropertiesListEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends FormatProperties2 e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss FormatProperties2 es, PokeChain es) => ToCStruct (FormatProperties2 es) where
  withCStruct :: FormatProperties2 es
-> (Ptr (FormatProperties2 es) -> IO b) -> IO b
withCStruct x :: FormatProperties2 es
x f :: Ptr (FormatProperties2 es) -> IO b
f = Int -> Int -> (Ptr (FormatProperties2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr (FormatProperties2 es) -> IO b) -> IO b)
-> (Ptr (FormatProperties2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (FormatProperties2 es)
p -> Ptr (FormatProperties2 es) -> FormatProperties2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (FormatProperties2 es)
p FormatProperties2 es
x (Ptr (FormatProperties2 es) -> IO b
f Ptr (FormatProperties2 es)
p)
  pokeCStruct :: Ptr (FormatProperties2 es) -> FormatProperties2 es -> IO b -> IO b
pokeCStruct p :: Ptr (FormatProperties2 es)
p FormatProperties2{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FormatProperties2 es)
p Ptr (FormatProperties2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FORMAT_PROPERTIES_2)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FormatProperties2 es)
p Ptr (FormatProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr FormatProperties -> FormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (FormatProperties2 es)
p Ptr (FormatProperties2 es) -> Int -> Ptr FormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr FormatProperties)) (FormatProperties
formatProperties) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (FormatProperties2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (FormatProperties2 es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FormatProperties2 es)
p Ptr (FormatProperties2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FORMAT_PROPERTIES_2)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FormatProperties2 es)
p Ptr (FormatProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr FormatProperties -> FormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (FormatProperties2 es)
p Ptr (FormatProperties2 es) -> Int -> Ptr FormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr FormatProperties)) (FormatProperties
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss FormatProperties2 es, PeekChain es) => FromCStruct (FormatProperties2 es) where
  peekCStruct :: Ptr (FormatProperties2 es) -> IO (FormatProperties2 es)
peekCStruct p :: Ptr (FormatProperties2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (FormatProperties2 es)
p Ptr (FormatProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    FormatProperties
formatProperties <- Ptr FormatProperties -> IO FormatProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @FormatProperties ((Ptr (FormatProperties2 es)
p Ptr (FormatProperties2 es) -> Int -> Ptr FormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr FormatProperties))
    FormatProperties2 es -> IO (FormatProperties2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FormatProperties2 es -> IO (FormatProperties2 es))
-> FormatProperties2 es -> IO (FormatProperties2 es)
forall a b. (a -> b) -> a -> b
$ Chain es -> FormatProperties -> FormatProperties2 es
forall (es :: [*]).
Chain es -> FormatProperties -> FormatProperties2 es
FormatProperties2
             Chain es
next FormatProperties
formatProperties

instance es ~ '[] => Zero (FormatProperties2 es) where
  zero :: FormatProperties2 es
zero = Chain es -> FormatProperties -> FormatProperties2 es
forall (es :: [*]).
Chain es -> FormatProperties -> FormatProperties2 es
FormatProperties2
           ()
           FormatProperties
forall a. Zero a => a
zero


-- | VkImageFormatProperties2 - Structure specifying an image format
-- properties
--
-- = Description
--
-- If the combination of parameters to
-- 'getPhysicalDeviceImageFormatProperties2' is not supported by the
-- implementation for use in 'Vulkan.Core10.Image.createImage', then all
-- members of @imageFormatProperties@ will be filled with zero.
--
-- Note
--
-- Filling @imageFormatProperties@ with zero for unsupported formats is an
-- exception to the usual rule that output structures have undefined
-- contents on error. This exception was unintentional, but is preserved
-- for backwards compatibility. This exeption only applies to
-- @imageFormatProperties@, not @sType@, @pNext@, or any structures chained
-- from @pNext@.
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_IMAGE_FORMAT_PROPERTIES_2'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AndroidHardwareBufferUsageANDROID',
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.ExternalImageFormatProperties',
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT',
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.SamplerYcbcrConversionImageFormatProperties',
--     or
--     'Vulkan.Extensions.VK_AMD_texture_gather_bias_lod.TextureLODGatherFormatPropertiesAMD'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- = See Also
--
-- 'Vulkan.Core10.DeviceInitialization.ImageFormatProperties',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceImageFormatProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2KHR'
data ImageFormatProperties2 (es :: [Type]) = ImageFormatProperties2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    -- The @pNext@ chain of 'ImageFormatProperties2' is used to allow the
    -- specification of additional capabilities to be returned from
    -- 'getPhysicalDeviceImageFormatProperties2'.
    ImageFormatProperties2 es -> Chain es
next :: Chain es
  , -- | @imageFormatProperties@ is a
    -- 'Vulkan.Core10.DeviceInitialization.ImageFormatProperties' structure in
    -- which capabilities are returned.
    ImageFormatProperties2 es -> ImageFormatProperties
imageFormatProperties :: ImageFormatProperties
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (ImageFormatProperties2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (ImageFormatProperties2 es)

instance Extensible ImageFormatProperties2 where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_IMAGE_FORMAT_PROPERTIES_2
  setNext :: ImageFormatProperties2 ds -> Chain es -> ImageFormatProperties2 es
setNext x :: ImageFormatProperties2 ds
x next :: Chain es
next = ImageFormatProperties2 ds
x{$sel:next:ImageFormatProperties2 :: Chain es
next = Chain es
next}
  getNext :: ImageFormatProperties2 es -> Chain es
getNext ImageFormatProperties2{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends ImageFormatProperties2 e => b) -> Maybe b
  extends :: proxy e -> (Extends ImageFormatProperties2 e => b) -> Maybe b
extends _ f :: Extends ImageFormatProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable FilterCubicImageViewImageFormatPropertiesEXT) =>
Maybe (e :~: FilterCubicImageViewImageFormatPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @FilterCubicImageViewImageFormatPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageFormatProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable AndroidHardwareBufferUsageANDROID) =>
Maybe (e :~: AndroidHardwareBufferUsageANDROID)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @AndroidHardwareBufferUsageANDROID = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageFormatProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable TextureLODGatherFormatPropertiesAMD) =>
Maybe (e :~: TextureLODGatherFormatPropertiesAMD)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @TextureLODGatherFormatPropertiesAMD = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageFormatProperties2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable SamplerYcbcrConversionImageFormatProperties) =>
Maybe (e :~: SamplerYcbcrConversionImageFormatProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @SamplerYcbcrConversionImageFormatProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageFormatProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable ExternalImageFormatProperties) =>
Maybe (e :~: ExternalImageFormatProperties)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExternalImageFormatProperties = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends ImageFormatProperties2 e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss ImageFormatProperties2 es, PokeChain es) => ToCStruct (ImageFormatProperties2 es) where
  withCStruct :: ImageFormatProperties2 es
-> (Ptr (ImageFormatProperties2 es) -> IO b) -> IO b
withCStruct x :: ImageFormatProperties2 es
x f :: Ptr (ImageFormatProperties2 es) -> IO b
f = Int -> Int -> (Ptr (ImageFormatProperties2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr (ImageFormatProperties2 es) -> IO b) -> IO b)
-> (Ptr (ImageFormatProperties2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (ImageFormatProperties2 es)
p -> Ptr (ImageFormatProperties2 es)
-> ImageFormatProperties2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (ImageFormatProperties2 es)
p ImageFormatProperties2 es
x (Ptr (ImageFormatProperties2 es) -> IO b
f Ptr (ImageFormatProperties2 es)
p)
  pokeCStruct :: Ptr (ImageFormatProperties2 es)
-> ImageFormatProperties2 es -> IO b -> IO b
pokeCStruct p :: Ptr (ImageFormatProperties2 es)
p ImageFormatProperties2{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageFormatProperties2 es)
p Ptr (ImageFormatProperties2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_FORMAT_PROPERTIES_2)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageFormatProperties2 es)
p Ptr (ImageFormatProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageFormatProperties -> ImageFormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageFormatProperties2 es)
p Ptr (ImageFormatProperties2 es) -> Int -> Ptr ImageFormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageFormatProperties)) (ImageFormatProperties
imageFormatProperties) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (ImageFormatProperties2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (ImageFormatProperties2 es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageFormatProperties2 es)
p Ptr (ImageFormatProperties2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_IMAGE_FORMAT_PROPERTIES_2)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (ImageFormatProperties2 es)
p Ptr (ImageFormatProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageFormatProperties -> ImageFormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (ImageFormatProperties2 es)
p Ptr (ImageFormatProperties2 es) -> Int -> Ptr ImageFormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageFormatProperties)) (ImageFormatProperties
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss ImageFormatProperties2 es, PeekChain es) => FromCStruct (ImageFormatProperties2 es) where
  peekCStruct :: Ptr (ImageFormatProperties2 es) -> IO (ImageFormatProperties2 es)
peekCStruct p :: Ptr (ImageFormatProperties2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (ImageFormatProperties2 es)
p Ptr (ImageFormatProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    ImageFormatProperties
imageFormatProperties <- Ptr ImageFormatProperties -> IO ImageFormatProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @ImageFormatProperties ((Ptr (ImageFormatProperties2 es)
p Ptr (ImageFormatProperties2 es) -> Int -> Ptr ImageFormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr ImageFormatProperties))
    ImageFormatProperties2 es -> IO (ImageFormatProperties2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (ImageFormatProperties2 es -> IO (ImageFormatProperties2 es))
-> ImageFormatProperties2 es -> IO (ImageFormatProperties2 es)
forall a b. (a -> b) -> a -> b
$ Chain es -> ImageFormatProperties -> ImageFormatProperties2 es
forall (es :: [*]).
Chain es -> ImageFormatProperties -> ImageFormatProperties2 es
ImageFormatProperties2
             Chain es
next ImageFormatProperties
imageFormatProperties

instance es ~ '[] => Zero (ImageFormatProperties2 es) where
  zero :: ImageFormatProperties2 es
zero = Chain es -> ImageFormatProperties -> ImageFormatProperties2 es
forall (es :: [*]).
Chain es -> ImageFormatProperties -> ImageFormatProperties2 es
ImageFormatProperties2
           ()
           ImageFormatProperties
forall a. Zero a => a
zero


-- | VkPhysicalDeviceImageFormatInfo2 - Structure specifying image creation
-- parameters
--
-- = Description
--
-- The members of 'PhysicalDeviceImageFormatInfo2' correspond to the
-- arguments to
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceImageFormatProperties',
-- with @sType@ and @pNext@ added for extensibility.
--
-- == Valid Usage
--
-- -   @tiling@ /must/ be
--     'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT'
--     if and only if the @pNext@ chain includes
--     'Vulkan.Extensions.VK_EXT_image_drm_format_modifier.PhysicalDeviceImageDrmFormatModifierInfoEXT'
--
-- -   If @tiling@ is
--     'Vulkan.Core10.Enums.ImageTiling.IMAGE_TILING_DRM_FORMAT_MODIFIER_EXT'
--     and @flags@ contains
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_MUTABLE_FORMAT_BIT',
--     then the @pNext@ chain /must/ include a
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo'
--     structure with non-zero @viewFormatCount@
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_FORMAT_INFO_2'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Core12.Promoted_From_VK_KHR_image_format_list.ImageFormatListCreateInfo',
--     'Vulkan.Core12.Promoted_From_VK_EXT_separate_stencil_usage.ImageStencilUsageCreateInfo',
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.PhysicalDeviceExternalImageFormatInfo',
--     'Vulkan.Extensions.VK_EXT_image_drm_format_modifier.PhysicalDeviceImageDrmFormatModifierInfoEXT',
--     or
--     'Vulkan.Extensions.VK_EXT_filter_cubic.PhysicalDeviceImageViewImageFormatInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @format@ /must/ be a valid 'Vulkan.Core10.Enums.Format.Format' value
--
-- -   @type@ /must/ be a valid 'Vulkan.Core10.Enums.ImageType.ImageType'
--     value
--
-- -   @tiling@ /must/ be a valid
--     'Vulkan.Core10.Enums.ImageTiling.ImageTiling' value
--
-- -   @usage@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits' values
--
-- -   @usage@ /must/ not be @0@
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.ImageCreateFlagBits' values
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'Vulkan.Core10.Enums.ImageCreateFlagBits.ImageCreateFlags',
-- 'Vulkan.Core10.Enums.ImageTiling.ImageTiling',
-- 'Vulkan.Core10.Enums.ImageType.ImageType',
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceImageFormatProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2KHR'
data PhysicalDeviceImageFormatInfo2 (es :: [Type]) = PhysicalDeviceImageFormatInfo2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    -- The @pNext@ chain of 'PhysicalDeviceImageFormatInfo2' is used to provide
    -- additional image parameters to
    -- 'getPhysicalDeviceImageFormatProperties2'.
    PhysicalDeviceImageFormatInfo2 es -> Chain es
next :: Chain es
  , -- | @format@ is a 'Vulkan.Core10.Enums.Format.Format' value indicating the
    -- image format, corresponding to
    -- 'Vulkan.Core10.Image.ImageCreateInfo'::@format@.
    PhysicalDeviceImageFormatInfo2 es -> Format
format :: Format
  , -- | @type@ is a 'Vulkan.Core10.Enums.ImageType.ImageType' value indicating
    -- the image type, corresponding to
    -- 'Vulkan.Core10.Image.ImageCreateInfo'::@imageType@.
    PhysicalDeviceImageFormatInfo2 es -> ImageType
type' :: ImageType
  , -- | @tiling@ is a 'Vulkan.Core10.Enums.ImageTiling.ImageTiling' value
    -- indicating the image tiling, corresponding to
    -- 'Vulkan.Core10.Image.ImageCreateInfo'::@tiling@.
    PhysicalDeviceImageFormatInfo2 es -> ImageTiling
tiling :: ImageTiling
  , -- | @usage@ is a bitmask of
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits' indicating
    -- the intended usage of the image, corresponding to
    -- 'Vulkan.Core10.Image.ImageCreateInfo'::@usage@.
    PhysicalDeviceImageFormatInfo2 es -> ImageUsageFlags
usage :: ImageUsageFlags
  , -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.ImageCreateFlagBits' indicating
    -- additional parameters of the image, corresponding to
    -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@.
    PhysicalDeviceImageFormatInfo2 es -> ImageCreateFlags
flags :: ImageCreateFlags
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceImageFormatInfo2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PhysicalDeviceImageFormatInfo2 es)

instance Extensible PhysicalDeviceImageFormatInfo2 where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_FORMAT_INFO_2
  setNext :: PhysicalDeviceImageFormatInfo2 ds
-> Chain es -> PhysicalDeviceImageFormatInfo2 es
setNext x :: PhysicalDeviceImageFormatInfo2 ds
x next :: Chain es
next = PhysicalDeviceImageFormatInfo2 ds
x{$sel:next:PhysicalDeviceImageFormatInfo2 :: Chain es
next = Chain es
next}
  getNext :: PhysicalDeviceImageFormatInfo2 es -> Chain es
getNext PhysicalDeviceImageFormatInfo2{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends PhysicalDeviceImageFormatInfo2 e => b) -> Maybe b
  extends :: proxy e
-> (Extends PhysicalDeviceImageFormatInfo2 e => b) -> Maybe b
extends _ f :: Extends PhysicalDeviceImageFormatInfo2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceImageViewImageFormatInfoEXT) =>
Maybe (e :~: PhysicalDeviceImageViewImageFormatInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceImageViewImageFormatInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceImageFormatInfo2 e => b
f
    | Just Refl <- (Typeable e, Typeable ImageStencilUsageCreateInfo) =>
Maybe (e :~: ImageStencilUsageCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageStencilUsageCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceImageFormatInfo2 e => b
f
    | Just Refl <- (Typeable e,
 Typeable PhysicalDeviceImageDrmFormatModifierInfoEXT) =>
Maybe (e :~: PhysicalDeviceImageDrmFormatModifierInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceImageDrmFormatModifierInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceImageFormatInfo2 e => b
f
    | Just Refl <- (Typeable e, Typeable ImageFormatListCreateInfo) =>
Maybe (e :~: ImageFormatListCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImageFormatListCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceImageFormatInfo2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceExternalImageFormatInfo) =>
Maybe (e :~: PhysicalDeviceExternalImageFormatInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceExternalImageFormatInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceImageFormatInfo2 e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss PhysicalDeviceImageFormatInfo2 es, PokeChain es) => ToCStruct (PhysicalDeviceImageFormatInfo2 es) where
  withCStruct :: PhysicalDeviceImageFormatInfo2 es
-> (Ptr (PhysicalDeviceImageFormatInfo2 es) -> IO b) -> IO b
withCStruct x :: PhysicalDeviceImageFormatInfo2 es
x f :: Ptr (PhysicalDeviceImageFormatInfo2 es) -> IO b
f = Int
-> Int -> (Ptr (PhysicalDeviceImageFormatInfo2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr (PhysicalDeviceImageFormatInfo2 es) -> IO b) -> IO b)
-> (Ptr (PhysicalDeviceImageFormatInfo2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PhysicalDeviceImageFormatInfo2 es)
p -> Ptr (PhysicalDeviceImageFormatInfo2 es)
-> PhysicalDeviceImageFormatInfo2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PhysicalDeviceImageFormatInfo2 es)
p PhysicalDeviceImageFormatInfo2 es
x (Ptr (PhysicalDeviceImageFormatInfo2 es) -> IO b
f Ptr (PhysicalDeviceImageFormatInfo2 es)
p)
  pokeCStruct :: Ptr (PhysicalDeviceImageFormatInfo2 es)
-> PhysicalDeviceImageFormatInfo2 es -> IO b -> IO b
pokeCStruct p :: Ptr (PhysicalDeviceImageFormatInfo2 es)
p PhysicalDeviceImageFormatInfo2{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_FORMAT_INFO_2)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format)) (Format
format)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageType -> ImageType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr ImageType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageType)) (ImageType
type')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageTiling -> ImageTiling -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr ImageTiling
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageTiling)) (ImageTiling
tiling)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es)
-> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageUsageFlags)) (ImageUsageFlags
usage)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageCreateFlags -> ImageCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es)
-> Int -> Ptr ImageCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageCreateFlags)) (ImageCreateFlags
flags)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PhysicalDeviceImageFormatInfo2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PhysicalDeviceImageFormatInfo2 es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_IMAGE_FORMAT_INFO_2)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageType -> ImageType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr ImageType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageType)) (ImageType
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageTiling -> ImageTiling -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr ImageTiling
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageTiling)) (ImageTiling
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es)
-> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageUsageFlags)) (ImageUsageFlags
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PhysicalDeviceImageFormatInfo2 es, PeekChain es) => FromCStruct (PhysicalDeviceImageFormatInfo2 es) where
  peekCStruct :: Ptr (PhysicalDeviceImageFormatInfo2 es)
-> IO (PhysicalDeviceImageFormatInfo2 es)
peekCStruct p :: Ptr (PhysicalDeviceImageFormatInfo2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format))
    ImageType
type' <- Ptr ImageType -> IO ImageType
forall a. Storable a => Ptr a -> IO a
peek @ImageType ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr ImageType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageType))
    ImageTiling
tiling <- Ptr ImageTiling -> IO ImageTiling
forall a. Storable a => Ptr a -> IO a
peek @ImageTiling ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es) -> Int -> Ptr ImageTiling
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr ImageTiling))
    ImageUsageFlags
usage <- Ptr ImageUsageFlags -> IO ImageUsageFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageUsageFlags ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es)
-> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageUsageFlags))
    ImageCreateFlags
flags <- Ptr ImageCreateFlags -> IO ImageCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageCreateFlags ((Ptr (PhysicalDeviceImageFormatInfo2 es)
p Ptr (PhysicalDeviceImageFormatInfo2 es)
-> Int -> Ptr ImageCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageCreateFlags))
    PhysicalDeviceImageFormatInfo2 es
-> IO (PhysicalDeviceImageFormatInfo2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceImageFormatInfo2 es
 -> IO (PhysicalDeviceImageFormatInfo2 es))
-> PhysicalDeviceImageFormatInfo2 es
-> IO (PhysicalDeviceImageFormatInfo2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> Format
-> ImageType
-> ImageTiling
-> ImageUsageFlags
-> ImageCreateFlags
-> PhysicalDeviceImageFormatInfo2 es
forall (es :: [*]).
Chain es
-> Format
-> ImageType
-> ImageTiling
-> ImageUsageFlags
-> ImageCreateFlags
-> PhysicalDeviceImageFormatInfo2 es
PhysicalDeviceImageFormatInfo2
             Chain es
next Format
format ImageType
type' ImageTiling
tiling ImageUsageFlags
usage ImageCreateFlags
flags

instance es ~ '[] => Zero (PhysicalDeviceImageFormatInfo2 es) where
  zero :: PhysicalDeviceImageFormatInfo2 es
zero = Chain es
-> Format
-> ImageType
-> ImageTiling
-> ImageUsageFlags
-> ImageCreateFlags
-> PhysicalDeviceImageFormatInfo2 es
forall (es :: [*]).
Chain es
-> Format
-> ImageType
-> ImageTiling
-> ImageUsageFlags
-> ImageCreateFlags
-> PhysicalDeviceImageFormatInfo2 es
PhysicalDeviceImageFormatInfo2
           ()
           Format
forall a. Zero a => a
zero
           ImageType
forall a. Zero a => a
zero
           ImageTiling
forall a. Zero a => a
zero
           ImageUsageFlags
forall a. Zero a => a
zero
           ImageCreateFlags
forall a. Zero a => a
zero


-- | VkQueueFamilyProperties2 - Structure providing information about a queue
-- family
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_QUEUE_FAMILY_PROPERTIES_2'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_NV_device_diagnostic_checkpoints.QueueFamilyCheckpointPropertiesNV'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- = See Also
--
-- 'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceQueueFamilyProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceQueueFamilyProperties2KHR'
data QueueFamilyProperties2 (es :: [Type]) = QueueFamilyProperties2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    QueueFamilyProperties2 es -> Chain es
next :: Chain es
  , -- | @queueFamilyProperties@ is a
    -- 'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties' structure
    -- which is populated with the same values as in
    -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceQueueFamilyProperties'.
    QueueFamilyProperties2 es -> QueueFamilyProperties
queueFamilyProperties :: QueueFamilyProperties
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (QueueFamilyProperties2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (QueueFamilyProperties2 es)

instance Extensible QueueFamilyProperties2 where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_QUEUE_FAMILY_PROPERTIES_2
  setNext :: QueueFamilyProperties2 ds -> Chain es -> QueueFamilyProperties2 es
setNext x :: QueueFamilyProperties2 ds
x next :: Chain es
next = QueueFamilyProperties2 ds
x{$sel:next:QueueFamilyProperties2 :: Chain es
next = Chain es
next}
  getNext :: QueueFamilyProperties2 es -> Chain es
getNext QueueFamilyProperties2{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends QueueFamilyProperties2 e => b) -> Maybe b
  extends :: proxy e -> (Extends QueueFamilyProperties2 e => b) -> Maybe b
extends _ f :: Extends QueueFamilyProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable QueueFamilyCheckpointPropertiesNV) =>
Maybe (e :~: QueueFamilyCheckpointPropertiesNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @QueueFamilyCheckpointPropertiesNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends QueueFamilyProperties2 e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss QueueFamilyProperties2 es, PokeChain es) => ToCStruct (QueueFamilyProperties2 es) where
  withCStruct :: QueueFamilyProperties2 es
-> (Ptr (QueueFamilyProperties2 es) -> IO b) -> IO b
withCStruct x :: QueueFamilyProperties2 es
x f :: Ptr (QueueFamilyProperties2 es) -> IO b
f = Int -> Int -> (Ptr (QueueFamilyProperties2 es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr (QueueFamilyProperties2 es) -> IO b) -> IO b)
-> (Ptr (QueueFamilyProperties2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (QueueFamilyProperties2 es)
p -> Ptr (QueueFamilyProperties2 es)
-> QueueFamilyProperties2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (QueueFamilyProperties2 es)
p QueueFamilyProperties2 es
x (Ptr (QueueFamilyProperties2 es) -> IO b
f Ptr (QueueFamilyProperties2 es)
p)
  pokeCStruct :: Ptr (QueueFamilyProperties2 es)
-> QueueFamilyProperties2 es -> IO b -> IO b
pokeCStruct p :: Ptr (QueueFamilyProperties2 es)
p QueueFamilyProperties2{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueueFamilyProperties2 es)
p Ptr (QueueFamilyProperties2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUEUE_FAMILY_PROPERTIES_2)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueueFamilyProperties2 es)
p Ptr (QueueFamilyProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr QueueFamilyProperties -> QueueFamilyProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (QueueFamilyProperties2 es)
p Ptr (QueueFamilyProperties2 es) -> Int -> Ptr QueueFamilyProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr QueueFamilyProperties)) (QueueFamilyProperties
queueFamilyProperties) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (QueueFamilyProperties2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (QueueFamilyProperties2 es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueueFamilyProperties2 es)
p Ptr (QueueFamilyProperties2 es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_QUEUE_FAMILY_PROPERTIES_2)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (QueueFamilyProperties2 es)
p Ptr (QueueFamilyProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr QueueFamilyProperties -> QueueFamilyProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (QueueFamilyProperties2 es)
p Ptr (QueueFamilyProperties2 es) -> Int -> Ptr QueueFamilyProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr QueueFamilyProperties)) (QueueFamilyProperties
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss QueueFamilyProperties2 es, PeekChain es) => FromCStruct (QueueFamilyProperties2 es) where
  peekCStruct :: Ptr (QueueFamilyProperties2 es) -> IO (QueueFamilyProperties2 es)
peekCStruct p :: Ptr (QueueFamilyProperties2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (QueueFamilyProperties2 es)
p Ptr (QueueFamilyProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    QueueFamilyProperties
queueFamilyProperties <- Ptr QueueFamilyProperties -> IO QueueFamilyProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @QueueFamilyProperties ((Ptr (QueueFamilyProperties2 es)
p Ptr (QueueFamilyProperties2 es) -> Int -> Ptr QueueFamilyProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr QueueFamilyProperties))
    QueueFamilyProperties2 es -> IO (QueueFamilyProperties2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (QueueFamilyProperties2 es -> IO (QueueFamilyProperties2 es))
-> QueueFamilyProperties2 es -> IO (QueueFamilyProperties2 es)
forall a b. (a -> b) -> a -> b
$ Chain es -> QueueFamilyProperties -> QueueFamilyProperties2 es
forall (es :: [*]).
Chain es -> QueueFamilyProperties -> QueueFamilyProperties2 es
QueueFamilyProperties2
             Chain es
next QueueFamilyProperties
queueFamilyProperties

instance es ~ '[] => Zero (QueueFamilyProperties2 es) where
  zero :: QueueFamilyProperties2 es
zero = Chain es -> QueueFamilyProperties -> QueueFamilyProperties2 es
forall (es :: [*]).
Chain es -> QueueFamilyProperties -> QueueFamilyProperties2 es
QueueFamilyProperties2
           ()
           QueueFamilyProperties
forall a. Zero a => a
zero


-- | VkPhysicalDeviceMemoryProperties2 - Structure specifying physical device
-- memory properties
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PROPERTIES_2'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_memory_budget.PhysicalDeviceMemoryBudgetPropertiesEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- = See Also
--
-- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceMemoryProperties',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceMemoryProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceMemoryProperties2KHR'
data PhysicalDeviceMemoryProperties2 (es :: [Type]) = PhysicalDeviceMemoryProperties2
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    PhysicalDeviceMemoryProperties2 es -> Chain es
next :: Chain es
  , -- | @memoryProperties@ is a
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceMemoryProperties'
    -- structure which is populated with the same values as in
    -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceMemoryProperties'.
    PhysicalDeviceMemoryProperties2 es
-> PhysicalDeviceMemoryProperties
memoryProperties :: PhysicalDeviceMemoryProperties
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMemoryProperties2 (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (PhysicalDeviceMemoryProperties2 es)

instance Extensible PhysicalDeviceMemoryProperties2 where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PROPERTIES_2
  setNext :: PhysicalDeviceMemoryProperties2 ds
-> Chain es -> PhysicalDeviceMemoryProperties2 es
setNext x :: PhysicalDeviceMemoryProperties2 ds
x next :: Chain es
next = PhysicalDeviceMemoryProperties2 ds
x{$sel:next:PhysicalDeviceMemoryProperties2 :: Chain es
next = Chain es
next}
  getNext :: PhysicalDeviceMemoryProperties2 es -> Chain es
getNext PhysicalDeviceMemoryProperties2{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends PhysicalDeviceMemoryProperties2 e => b) -> Maybe b
  extends :: proxy e
-> (Extends PhysicalDeviceMemoryProperties2 e => b) -> Maybe b
extends _ f :: Extends PhysicalDeviceMemoryProperties2 e => b
f
    | Just Refl <- (Typeable e, Typeable PhysicalDeviceMemoryBudgetPropertiesEXT) =>
Maybe (e :~: PhysicalDeviceMemoryBudgetPropertiesEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PhysicalDeviceMemoryBudgetPropertiesEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends PhysicalDeviceMemoryProperties2 e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss PhysicalDeviceMemoryProperties2 es, PokeChain es) => ToCStruct (PhysicalDeviceMemoryProperties2 es) where
  withCStruct :: PhysicalDeviceMemoryProperties2 es
-> (Ptr (PhysicalDeviceMemoryProperties2 es) -> IO b) -> IO b
withCStruct x :: PhysicalDeviceMemoryProperties2 es
x f :: Ptr (PhysicalDeviceMemoryProperties2 es) -> IO b
f = Int
-> Int
-> (Ptr (PhysicalDeviceMemoryProperties2 es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 536 8 ((Ptr (PhysicalDeviceMemoryProperties2 es) -> IO b) -> IO b)
-> (Ptr (PhysicalDeviceMemoryProperties2 es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (PhysicalDeviceMemoryProperties2 es)
p -> Ptr (PhysicalDeviceMemoryProperties2 es)
-> PhysicalDeviceMemoryProperties2 es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (PhysicalDeviceMemoryProperties2 es)
p PhysicalDeviceMemoryProperties2 es
x (Ptr (PhysicalDeviceMemoryProperties2 es) -> IO b
f Ptr (PhysicalDeviceMemoryProperties2 es)
p)
  pokeCStruct :: Ptr (PhysicalDeviceMemoryProperties2 es)
-> PhysicalDeviceMemoryProperties2 es -> IO b -> IO b
pokeCStruct p :: Ptr (PhysicalDeviceMemoryProperties2 es)
p PhysicalDeviceMemoryProperties2{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceMemoryProperties2 es)
p Ptr (PhysicalDeviceMemoryProperties2 es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PROPERTIES_2)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceMemoryProperties2 es)
p Ptr (PhysicalDeviceMemoryProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDeviceMemoryProperties
-> PhysicalDeviceMemoryProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (PhysicalDeviceMemoryProperties2 es)
p Ptr (PhysicalDeviceMemoryProperties2 es)
-> Int -> Ptr PhysicalDeviceMemoryProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceMemoryProperties)) (PhysicalDeviceMemoryProperties
memoryProperties) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 536
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (PhysicalDeviceMemoryProperties2 es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (PhysicalDeviceMemoryProperties2 es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceMemoryProperties2 es)
p Ptr (PhysicalDeviceMemoryProperties2 es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PROPERTIES_2)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (PhysicalDeviceMemoryProperties2 es)
p Ptr (PhysicalDeviceMemoryProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDeviceMemoryProperties
-> PhysicalDeviceMemoryProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (PhysicalDeviceMemoryProperties2 es)
p Ptr (PhysicalDeviceMemoryProperties2 es)
-> Int -> Ptr PhysicalDeviceMemoryProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceMemoryProperties)) (PhysicalDeviceMemoryProperties
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance (Extendss PhysicalDeviceMemoryProperties2 es, PeekChain es) => FromCStruct (PhysicalDeviceMemoryProperties2 es) where
  peekCStruct :: Ptr (PhysicalDeviceMemoryProperties2 es)
-> IO (PhysicalDeviceMemoryProperties2 es)
peekCStruct p :: Ptr (PhysicalDeviceMemoryProperties2 es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (PhysicalDeviceMemoryProperties2 es)
p Ptr (PhysicalDeviceMemoryProperties2 es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    PhysicalDeviceMemoryProperties
memoryProperties <- Ptr PhysicalDeviceMemoryProperties
-> IO PhysicalDeviceMemoryProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PhysicalDeviceMemoryProperties ((Ptr (PhysicalDeviceMemoryProperties2 es)
p Ptr (PhysicalDeviceMemoryProperties2 es)
-> Int -> Ptr PhysicalDeviceMemoryProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PhysicalDeviceMemoryProperties))
    PhysicalDeviceMemoryProperties2 es
-> IO (PhysicalDeviceMemoryProperties2 es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMemoryProperties2 es
 -> IO (PhysicalDeviceMemoryProperties2 es))
-> PhysicalDeviceMemoryProperties2 es
-> IO (PhysicalDeviceMemoryProperties2 es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PhysicalDeviceMemoryProperties
-> PhysicalDeviceMemoryProperties2 es
forall (es :: [*]).
Chain es
-> PhysicalDeviceMemoryProperties
-> PhysicalDeviceMemoryProperties2 es
PhysicalDeviceMemoryProperties2
             Chain es
next PhysicalDeviceMemoryProperties
memoryProperties

instance es ~ '[] => Zero (PhysicalDeviceMemoryProperties2 es) where
  zero :: PhysicalDeviceMemoryProperties2 es
zero = Chain es
-> PhysicalDeviceMemoryProperties
-> PhysicalDeviceMemoryProperties2 es
forall (es :: [*]).
Chain es
-> PhysicalDeviceMemoryProperties
-> PhysicalDeviceMemoryProperties2 es
PhysicalDeviceMemoryProperties2
           ()
           PhysicalDeviceMemoryProperties
forall a. Zero a => a
zero


-- | VkSparseImageFormatProperties2 - Structure specifying sparse image
-- format properties
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageFormatProperties',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceSparseImageFormatProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceSparseImageFormatProperties2KHR'
data SparseImageFormatProperties2 = SparseImageFormatProperties2
  { -- | @properties@ is a
    -- 'Vulkan.Core10.SparseResourceMemoryManagement.SparseImageFormatProperties'
    -- structure which is populated with the same values as in
    -- 'Vulkan.Core10.SparseResourceMemoryManagement.getPhysicalDeviceSparseImageFormatProperties'.
    SparseImageFormatProperties2 -> SparseImageFormatProperties
properties :: SparseImageFormatProperties }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SparseImageFormatProperties2)
#endif
deriving instance Show SparseImageFormatProperties2

instance ToCStruct SparseImageFormatProperties2 where
  withCStruct :: SparseImageFormatProperties2
-> (("pProperties" ::: Ptr SparseImageFormatProperties2) -> IO b)
-> IO b
withCStruct x :: SparseImageFormatProperties2
x f :: ("pProperties" ::: Ptr SparseImageFormatProperties2) -> IO b
f = Int
-> Int
-> (("pProperties" ::: Ptr SparseImageFormatProperties2) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((("pProperties" ::: Ptr SparseImageFormatProperties2) -> IO b)
 -> IO b)
-> (("pProperties" ::: Ptr SparseImageFormatProperties2) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pProperties" ::: Ptr SparseImageFormatProperties2
p -> ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> SparseImageFormatProperties2 -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pProperties" ::: Ptr SparseImageFormatProperties2
p SparseImageFormatProperties2
x (("pProperties" ::: Ptr SparseImageFormatProperties2) -> IO b
f "pProperties" ::: Ptr SparseImageFormatProperties2
p)
  pokeCStruct :: ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> SparseImageFormatProperties2 -> IO b -> IO b
pokeCStruct p :: "pProperties" ::: Ptr SparseImageFormatProperties2
p SparseImageFormatProperties2{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr SparseImageFormatProperties2
p ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SPARSE_IMAGE_FORMAT_PROPERTIES_2)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr SparseImageFormatProperties2
p ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseImageFormatProperties
-> SparseImageFormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pProperties" ::: Ptr SparseImageFormatProperties2
p ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> Int -> Ptr SparseImageFormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SparseImageFormatProperties)) (SparseImageFormatProperties
properties) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> IO b -> IO b
pokeZeroCStruct p :: "pProperties" ::: Ptr SparseImageFormatProperties2
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr SparseImageFormatProperties2
p ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SPARSE_IMAGE_FORMAT_PROPERTIES_2)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pProperties" ::: Ptr SparseImageFormatProperties2
p ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr SparseImageFormatProperties
-> SparseImageFormatProperties -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pProperties" ::: Ptr SparseImageFormatProperties2
p ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> Int -> Ptr SparseImageFormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SparseImageFormatProperties)) (SparseImageFormatProperties
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance FromCStruct SparseImageFormatProperties2 where
  peekCStruct :: ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> IO SparseImageFormatProperties2
peekCStruct p :: "pProperties" ::: Ptr SparseImageFormatProperties2
p = do
    SparseImageFormatProperties
properties <- Ptr SparseImageFormatProperties -> IO SparseImageFormatProperties
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @SparseImageFormatProperties (("pProperties" ::: Ptr SparseImageFormatProperties2
p ("pProperties" ::: Ptr SparseImageFormatProperties2)
-> Int -> Ptr SparseImageFormatProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr SparseImageFormatProperties))
    SparseImageFormatProperties2 -> IO SparseImageFormatProperties2
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SparseImageFormatProperties2 -> IO SparseImageFormatProperties2)
-> SparseImageFormatProperties2 -> IO SparseImageFormatProperties2
forall a b. (a -> b) -> a -> b
$ SparseImageFormatProperties -> SparseImageFormatProperties2
SparseImageFormatProperties2
             SparseImageFormatProperties
properties

instance Zero SparseImageFormatProperties2 where
  zero :: SparseImageFormatProperties2
zero = SparseImageFormatProperties -> SparseImageFormatProperties2
SparseImageFormatProperties2
           SparseImageFormatProperties
forall a. Zero a => a
zero


-- | VkPhysicalDeviceSparseImageFormatInfo2 - Structure specifying sparse
-- image format inputs
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'Vulkan.Core10.Enums.ImageTiling.ImageTiling',
-- 'Vulkan.Core10.Enums.ImageType.ImageType',
-- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlags',
-- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getPhysicalDeviceSparseImageFormatProperties2',
-- 'Vulkan.Extensions.VK_KHR_get_physical_device_properties2.getPhysicalDeviceSparseImageFormatProperties2KHR'
data PhysicalDeviceSparseImageFormatInfo2 = PhysicalDeviceSparseImageFormatInfo2
  { -- | @format@ is the image format.
    --
    -- @format@ /must/ be a valid 'Vulkan.Core10.Enums.Format.Format' value
    PhysicalDeviceSparseImageFormatInfo2 -> Format
format :: Format
  , -- | @type@ is the dimensionality of image.
    --
    -- @type@ /must/ be a valid 'Vulkan.Core10.Enums.ImageType.ImageType' value
    PhysicalDeviceSparseImageFormatInfo2 -> ImageType
type' :: ImageType
  , -- | @samples@ is the number of samples per texel as defined in
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits'.
    --
    -- @samples@ /must/ be a bit value that is set in
    -- 'Vulkan.Core10.DeviceInitialization.ImageFormatProperties'::@sampleCounts@
    -- returned by
    -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceImageFormatProperties'
    -- with @format@, @type@, @tiling@, and @usage@ equal to those in this
    -- command and @flags@ equal to the value that is set in
    -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ when the image is created
    --
    -- @samples@ /must/ be a valid
    -- 'Vulkan.Core10.Enums.SampleCountFlagBits.SampleCountFlagBits' value
    PhysicalDeviceSparseImageFormatInfo2 -> SampleCountFlagBits
samples :: SampleCountFlagBits
  , -- | @usage@ is a bitmask describing the intended usage of the image.
    --
    -- @usage@ /must/ be a valid combination of
    -- 'Vulkan.Core10.Enums.ImageUsageFlagBits.ImageUsageFlagBits' values
    --
    -- @usage@ /must/ not be @0@
    PhysicalDeviceSparseImageFormatInfo2 -> ImageUsageFlags
usage :: ImageUsageFlags
  , -- | @tiling@ is the tiling arrangement of the texel blocks in memory.
    --
    -- @tiling@ /must/ be a valid 'Vulkan.Core10.Enums.ImageTiling.ImageTiling'
    -- value
    PhysicalDeviceSparseImageFormatInfo2 -> ImageTiling
tiling :: ImageTiling
  }
  deriving (Typeable, PhysicalDeviceSparseImageFormatInfo2
-> PhysicalDeviceSparseImageFormatInfo2 -> Bool
(PhysicalDeviceSparseImageFormatInfo2
 -> PhysicalDeviceSparseImageFormatInfo2 -> Bool)
-> (PhysicalDeviceSparseImageFormatInfo2
    -> PhysicalDeviceSparseImageFormatInfo2 -> Bool)
-> Eq PhysicalDeviceSparseImageFormatInfo2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceSparseImageFormatInfo2
-> PhysicalDeviceSparseImageFormatInfo2 -> Bool
$c/= :: PhysicalDeviceSparseImageFormatInfo2
-> PhysicalDeviceSparseImageFormatInfo2 -> Bool
== :: PhysicalDeviceSparseImageFormatInfo2
-> PhysicalDeviceSparseImageFormatInfo2 -> Bool
$c== :: PhysicalDeviceSparseImageFormatInfo2
-> PhysicalDeviceSparseImageFormatInfo2 -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceSparseImageFormatInfo2)
#endif
deriving instance Show PhysicalDeviceSparseImageFormatInfo2

instance ToCStruct PhysicalDeviceSparseImageFormatInfo2 where
  withCStruct :: PhysicalDeviceSparseImageFormatInfo2
-> (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
    -> IO b)
-> IO b
withCStruct x :: PhysicalDeviceSparseImageFormatInfo2
x f :: ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> IO b
f = Int
-> Int
-> (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
  -> IO b)
 -> IO b)
-> (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p -> ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> PhysicalDeviceSparseImageFormatInfo2 -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p PhysicalDeviceSparseImageFormatInfo2
x (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> IO b
f "pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p)
  pokeCStruct :: ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> PhysicalDeviceSparseImageFormatInfo2 -> IO b -> IO b
pokeCStruct p :: "pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p PhysicalDeviceSparseImageFormatInfo2{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SPARSE_IMAGE_FORMAT_INFO_2)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format)) (Format
format)
    Ptr ImageType -> ImageType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr ImageType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageType)) (ImageType
type')
    Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
samples)
    Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageUsageFlags)) (ImageUsageFlags
usage)
    Ptr ImageTiling -> ImageTiling -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr ImageTiling
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageTiling)) (ImageTiling
tiling)
    IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> IO b -> IO b
pokeZeroCStruct p :: "pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_SPARSE_IMAGE_FORMAT_INFO_2)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format)) (Format
forall a. Zero a => a
zero)
    Ptr ImageType -> ImageType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr ImageType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageType)) (ImageType
forall a. Zero a => a
zero)
    Ptr SampleCountFlagBits -> SampleCountFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlagBits)) (SampleCountFlagBits
forall a. Zero a => a
zero)
    Ptr ImageUsageFlags -> ImageUsageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageUsageFlags)) (ImageUsageFlags
forall a. Zero a => a
zero)
    Ptr ImageTiling -> ImageTiling -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr ImageTiling
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageTiling)) (ImageTiling
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceSparseImageFormatInfo2 where
  peekCStruct :: ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> IO PhysicalDeviceSparseImageFormatInfo2
peekCStruct p :: "pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p = do
    Format
format <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format))
    ImageType
type' <- Ptr ImageType -> IO ImageType
forall a. Storable a => Ptr a -> IO a
peek @ImageType (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr ImageType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr ImageType))
    SampleCountFlagBits
samples <- Ptr SampleCountFlagBits -> IO SampleCountFlagBits
forall a. Storable a => Ptr a -> IO a
peek @SampleCountFlagBits (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr SampleCountFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr SampleCountFlagBits))
    ImageUsageFlags
usage <- Ptr ImageUsageFlags -> IO ImageUsageFlags
forall a. Storable a => Ptr a -> IO a
peek @ImageUsageFlags (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr ImageUsageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr ImageUsageFlags))
    ImageTiling
tiling <- Ptr ImageTiling -> IO ImageTiling
forall a. Storable a => Ptr a -> IO a
peek @ImageTiling (("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2
p ("pFormatInfo" ::: Ptr PhysicalDeviceSparseImageFormatInfo2)
-> Int -> Ptr ImageTiling
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr ImageTiling))
    PhysicalDeviceSparseImageFormatInfo2
-> IO PhysicalDeviceSparseImageFormatInfo2
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceSparseImageFormatInfo2
 -> IO PhysicalDeviceSparseImageFormatInfo2)
-> PhysicalDeviceSparseImageFormatInfo2
-> IO PhysicalDeviceSparseImageFormatInfo2
forall a b. (a -> b) -> a -> b
$ Format
-> ImageType
-> SampleCountFlagBits
-> ImageUsageFlags
-> ImageTiling
-> PhysicalDeviceSparseImageFormatInfo2
PhysicalDeviceSparseImageFormatInfo2
             Format
format ImageType
type' SampleCountFlagBits
samples ImageUsageFlags
usage ImageTiling
tiling

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

instance Zero PhysicalDeviceSparseImageFormatInfo2 where
  zero :: PhysicalDeviceSparseImageFormatInfo2
zero = Format
-> ImageType
-> SampleCountFlagBits
-> ImageUsageFlags
-> ImageTiling
-> PhysicalDeviceSparseImageFormatInfo2
PhysicalDeviceSparseImageFormatInfo2
           Format
forall a. Zero a => a
zero
           ImageType
forall a. Zero a => a
zero
           SampleCountFlagBits
forall a. Zero a => a
zero
           ImageUsageFlags
forall a. Zero a => a
zero
           ImageTiling
forall a. Zero a => a
zero