{-# language CPP #-}
module Vulkan.Core10.Device  ( createDevice
                             , withDevice
                             , destroyDevice
                             , DeviceQueueCreateInfo(..)
                             , DeviceCreateInfo(..)
                             , Device(..)
                             , DeviceCreateFlags(..)
                             , DeviceQueueCreateFlagBits(..)
                             , DeviceQueueCreateFlags
                             ) 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 Foreign.Marshal.Utils (maybePeek)
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 Data.ByteString (packCString)
import Data.ByteString (useAsCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(CFloat))
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
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.ByteString (ByteString)
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.Dynamic (initDeviceCmds)
import Vulkan.CStruct.Extends (peekSomeCStruct)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyDevice))
import Vulkan.Core10.Enums.DeviceCreateFlags (DeviceCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_device_diagnostics_config (DeviceDiagnosticsConfigCreateInfoNV)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_group_creation (DeviceGroupDeviceCreateInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_AMD_memory_overallocation_behavior (DeviceMemoryOverallocationCreateInfoAMD)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_private_data (DevicePrivateDataCreateInfoEXT)
import Vulkan.Core10.Enums.DeviceQueueCreateFlagBits (DeviceQueueCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_global_priority (DeviceQueueGlobalPriorityCreateInfoEXT)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Dynamic (InstanceCmds(pVkCreateDevice))
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.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_NV_cooperative_matrix (PhysicalDeviceCooperativeMatrixFeaturesNV)
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_NV_dedicated_allocation_image_aliasing (PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_depth_clip_enable (PhysicalDeviceDepthClipEnableFeaturesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing (PhysicalDeviceDescriptorIndexingFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_device_generated_commands (PhysicalDeviceDeviceGeneratedCommandsFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_device_diagnostics_config (PhysicalDeviceDiagnosticsConfigFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_scissor_exclusive (PhysicalDeviceExclusiveScissorFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_extended_dynamic_state (PhysicalDeviceExtendedDynamicStateFeaturesEXT)
import Vulkan.Core10.DeviceInitialization (PhysicalDeviceFeatures)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2 (PhysicalDeviceFeatures2)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map2 (PhysicalDeviceFragmentDensityMap2FeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_density_map (PhysicalDeviceFragmentDensityMapFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_fragment_shader_barycentric (PhysicalDeviceFragmentShaderBarycentricFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_fragment_shader_interlock (PhysicalDeviceFragmentShaderInterlockFeaturesEXT)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset (PhysicalDeviceHostQueryResetFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_image_robustness (PhysicalDeviceImageRobustnessFeaturesEXT)
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_line_rasterization (PhysicalDeviceLineRasterizationFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_memory_priority (PhysicalDeviceMemoryPriorityFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_mesh_shader (PhysicalDeviceMeshShaderFeaturesNV)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_multiview (PhysicalDeviceMultiviewFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_performance_query (PhysicalDevicePerformanceQueryFeaturesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_pipeline_creation_cache_control (PhysicalDevicePipelineCreationCacheControlFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_pipeline_executable_properties (PhysicalDevicePipelineExecutablePropertiesFeaturesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_private_data (PhysicalDevicePrivateDataFeaturesEXT)
import {-# SOURCE #-} Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory (PhysicalDeviceProtectedMemoryFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_ray_tracing (PhysicalDeviceRayTracingFeaturesKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_representative_fragment_test (PhysicalDeviceRepresentativeFragmentTestFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_robustness2 (PhysicalDeviceRobustness2FeaturesEXT)
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_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_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.Core12.Promoted_From_VK_KHR_shader_subgroup_extended_types (PhysicalDeviceShaderSubgroupExtendedTypesFeatures)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_shading_rate_image (PhysicalDeviceShadingRateImageFeaturesNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_subgroup_size_control (PhysicalDeviceSubgroupSizeControlFeaturesEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_texel_buffer_alignment (PhysicalDeviceTexelBufferAlignmentFeaturesEXT)
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.Extensions.VK_EXT_transform_feedback (PhysicalDeviceTransformFeedbackFeaturesEXT)
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.Core12 (PhysicalDeviceVulkan11Features)
import {-# SOURCE #-} Vulkan.Core12 (PhysicalDeviceVulkan12Features)
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 Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_CREATE_INFO))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_QUEUE_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Enums.DeviceCreateFlags (DeviceCreateFlags(..))
import Vulkan.Core10.Enums.DeviceQueueCreateFlagBits (DeviceQueueCreateFlagBits(..))
import Vulkan.Core10.Enums.DeviceQueueCreateFlagBits (DeviceQueueCreateFlags)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateDevice
  :: FunPtr (Ptr PhysicalDevice_T -> Ptr (SomeStruct DeviceCreateInfo) -> Ptr AllocationCallbacks -> Ptr (Ptr Device_T) -> IO Result) -> Ptr PhysicalDevice_T -> Ptr (SomeStruct DeviceCreateInfo) -> Ptr AllocationCallbacks -> Ptr (Ptr Device_T) -> IO Result

-- | vkCreateDevice - Create a new device instance
--
-- = Description
--
-- 'createDevice' verifies that extensions and features requested in the
-- @ppEnabledExtensionNames@ and @pEnabledFeatures@ members of
-- @pCreateInfo@, respectively, are supported by the implementation. If any
-- requested extension is not supported, 'createDevice' /must/ return
-- 'Vulkan.Core10.Enums.Result.ERROR_EXTENSION_NOT_PRESENT'. If any
-- requested feature is not supported, 'createDevice' /must/ return
-- 'Vulkan.Core10.Enums.Result.ERROR_FEATURE_NOT_PRESENT'. Support for
-- extensions /can/ be checked before creating a device by querying
-- 'Vulkan.Core10.ExtensionDiscovery.enumerateDeviceExtensionProperties'.
-- Support for features /can/ similarly be checked by querying
-- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceFeatures'.
--
-- After verifying and enabling the extensions the
-- 'Vulkan.Core10.Handles.Device' object is created and returned to the
-- application. If a requested extension is only supported by a layer, both
-- the layer and the extension need to be specified at
-- 'Vulkan.Core10.DeviceInitialization.createInstance' time for the
-- creation to succeed.
--
-- Multiple logical devices /can/ be created from the same physical device.
-- Logical device creation /may/ fail due to lack of device-specific
-- resources (in addition to the other errors). If that occurs,
-- 'createDevice' will return
-- 'Vulkan.Core10.Enums.Result.ERROR_TOO_MANY_OBJECTS'.
--
-- == Valid Usage
--
-- -   All
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-extensions-extensiondependencies required extensions>
--     for each extension in the
--     'DeviceCreateInfo'::@ppEnabledExtensionNames@ list /must/ also be
--     present in that list
--
-- == Valid Usage (Implicit)
--
-- -   @physicalDevice@ /must/ be a valid
--     'Vulkan.Core10.Handles.PhysicalDevice' handle
--
-- -   @pCreateInfo@ /must/ be a valid pointer to a valid
--     'DeviceCreateInfo' structure
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pDevice@ /must/ be a valid pointer to a
--     'Vulkan.Core10.Handles.Device' handle
--
-- == 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_INITIALIZATION_FAILED'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_EXTENSION_NOT_PRESENT'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_FEATURE_NOT_PRESENT'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_TOO_MANY_OBJECTS'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'DeviceCreateInfo',
-- 'Vulkan.Core10.Handles.PhysicalDevice'
createDevice :: forall a io
              . (Extendss DeviceCreateInfo a, PokeChain a, MonadIO io)
             => -- | @physicalDevice@ /must/ be one of the device handles returned from a
                -- call to 'Vulkan.Core10.DeviceInitialization.enumeratePhysicalDevices'
                -- (see
                -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#devsandqueues-physical-device-enumeration Physical Device Enumeration>).
                PhysicalDevice
             -> -- | @pCreateInfo@ is a pointer to a 'DeviceCreateInfo' structure containing
                -- information about how to create the device.
                (DeviceCreateInfo a)
             -> -- | @pAllocator@ controls host memory allocation as described in the
                -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                -- chapter.
                ("allocator" ::: Maybe AllocationCallbacks)
             -> io (Device)
createDevice :: PhysicalDevice
-> DeviceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Device
createDevice physicalDevice :: PhysicalDevice
physicalDevice createInfo :: DeviceCreateInfo a
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO Device -> io Device
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Device -> io Device)
-> (ContT Device IO Device -> IO Device)
-> ContT Device IO Device
-> io Device
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Device IO Device -> IO Device
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Device IO Device -> io Device)
-> ContT Device IO Device -> io Device
forall a b. (a -> b) -> a -> b
$ do
  let cmds :: InstanceCmds
cmds = PhysicalDevice -> InstanceCmds
instanceCmds (PhysicalDevice
physicalDevice :: PhysicalDevice)
  let vkCreateDevicePtr :: FunPtr
  (Ptr PhysicalDevice_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDevice" ::: Ptr (Ptr Device_T))
   -> IO Result)
vkCreateDevicePtr = InstanceCmds
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pDevice" ::: Ptr (Ptr Device_T))
      -> IO Result)
pVkCreateDevice InstanceCmds
cmds
  IO () -> ContT Device IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Device IO ()) -> IO () -> ContT Device IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr PhysicalDevice_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDevice" ::: Ptr (Ptr Device_T))
   -> IO Result)
vkCreateDevicePtr FunPtr
  (Ptr PhysicalDevice_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDevice" ::: Ptr (Ptr Device_T))
   -> IO Result)
-> FunPtr
     (Ptr PhysicalDevice_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pDevice" ::: Ptr (Ptr Device_T))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr PhysicalDevice_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDevice" ::: Ptr (Ptr Device_T))
   -> 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 vkCreateDevice is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateDevice' :: Ptr PhysicalDevice_T
-> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pDevice" ::: Ptr (Ptr Device_T))
-> IO Result
vkCreateDevice' = FunPtr
  (Ptr PhysicalDevice_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDevice" ::: Ptr (Ptr Device_T))
   -> IO Result)
-> Ptr PhysicalDevice_T
-> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pDevice" ::: Ptr (Ptr Device_T))
-> IO Result
mkVkCreateDevice FunPtr
  (Ptr PhysicalDevice_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDevice" ::: Ptr (Ptr Device_T))
   -> IO Result)
vkCreateDevicePtr
  Ptr (DeviceCreateInfo a)
pCreateInfo <- ((Ptr (DeviceCreateInfo a) -> IO Device) -> IO Device)
-> ContT Device IO (Ptr (DeviceCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (DeviceCreateInfo a) -> IO Device) -> IO Device)
 -> ContT Device IO (Ptr (DeviceCreateInfo a)))
-> ((Ptr (DeviceCreateInfo a) -> IO Device) -> IO Device)
-> ContT Device IO (Ptr (DeviceCreateInfo a))
forall a b. (a -> b) -> a -> b
$ DeviceCreateInfo a
-> (Ptr (DeviceCreateInfo a) -> IO Device) -> IO Device
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DeviceCreateInfo a
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT Device IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Device)
 -> IO Device)
-> ContT Device IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Device)
  -> IO Device)
 -> ContT Device IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Device)
    -> IO Device)
-> ContT Device IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO Device)
-> IO Device
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pDevice" ::: Ptr (Ptr Device_T)
pPDevice <- ((("pDevice" ::: Ptr (Ptr Device_T)) -> IO Device) -> IO Device)
-> ContT Device IO ("pDevice" ::: Ptr (Ptr Device_T))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDevice" ::: Ptr (Ptr Device_T)) -> IO Device) -> IO Device)
 -> ContT Device IO ("pDevice" ::: Ptr (Ptr Device_T)))
-> ((("pDevice" ::: Ptr (Ptr Device_T)) -> IO Device) -> IO Device)
-> ContT Device IO ("pDevice" ::: Ptr (Ptr Device_T))
forall a b. (a -> b) -> a -> b
$ IO ("pDevice" ::: Ptr (Ptr Device_T))
-> (("pDevice" ::: Ptr (Ptr Device_T)) -> IO ())
-> (("pDevice" ::: Ptr (Ptr Device_T)) -> IO Device)
-> IO Device
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pDevice" ::: Ptr (Ptr Device_T))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr Device_T) 8) ("pDevice" ::: Ptr (Ptr Device_T)) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT Device IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Device IO Result)
-> IO Result -> ContT Device IO Result
forall a b. (a -> b) -> a -> b
$ Ptr PhysicalDevice_T
-> ("pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pDevice" ::: Ptr (Ptr Device_T))
-> IO Result
vkCreateDevice' (PhysicalDevice -> Ptr PhysicalDevice_T
physicalDeviceHandle (PhysicalDevice
physicalDevice)) (Ptr (DeviceCreateInfo a)
-> "pCreateInfo" ::: Ptr (SomeStruct DeviceCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (DeviceCreateInfo a)
pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pDevice" ::: Ptr (Ptr Device_T)
pPDevice)
  IO () -> ContT Device IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Device IO ()) -> IO () -> ContT Device 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))
  Ptr Device_T
pDevice <- IO (Ptr Device_T) -> ContT Device IO (Ptr Device_T)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (Ptr Device_T) -> ContT Device IO (Ptr Device_T))
-> IO (Ptr Device_T) -> ContT Device IO (Ptr Device_T)
forall a b. (a -> b) -> a -> b
$ ("pDevice" ::: Ptr (Ptr Device_T)) -> IO (Ptr Device_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Device_T) "pDevice" ::: Ptr (Ptr Device_T)
pPDevice
  Device
pDevice' <- IO Device -> ContT Device IO Device
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Device -> ContT Device IO Device)
-> IO Device -> ContT Device IO Device
forall a b. (a -> b) -> a -> b
$ (\h :: Ptr Device_T
h -> Ptr Device_T -> DeviceCmds -> Device
Device Ptr Device_T
h (DeviceCmds -> Device) -> IO DeviceCmds -> IO Device
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> InstanceCmds -> Ptr Device_T -> IO DeviceCmds
initDeviceCmds InstanceCmds
cmds Ptr Device_T
h) Ptr Device_T
pDevice
  Device -> ContT Device IO Device
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Device -> ContT Device IO Device)
-> Device -> ContT Device IO Device
forall a b. (a -> b) -> a -> b
$ (Device
pDevice')

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createDevice' and 'destroyDevice'
--
-- To ensure that 'destroyDevice' is always called: pass
-- 'Control.Exception.bracket' (or the allocate function from your
-- favourite resource management library) as the first argument.
-- To just extract the pair pass '(,)' as the first argument.
--
withDevice :: forall a io r . (Extendss DeviceCreateInfo a, PokeChain a, MonadIO io) => PhysicalDevice -> DeviceCreateInfo a -> Maybe AllocationCallbacks -> (io (Device) -> ((Device) -> io ()) -> r) -> r
withDevice :: PhysicalDevice
-> DeviceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io Device -> (Device -> io ()) -> r)
-> r
withDevice physicalDevice :: PhysicalDevice
physicalDevice pCreateInfo :: DeviceCreateInfo a
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io Device -> (Device -> io ()) -> r
b =
  io Device -> (Device -> io ()) -> r
b (PhysicalDevice
-> DeviceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Device
forall (a :: [*]) (io :: * -> *).
(Extendss DeviceCreateInfo a, PokeChain a, MonadIO io) =>
PhysicalDevice
-> DeviceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Device
createDevice PhysicalDevice
physicalDevice DeviceCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(Device
o0) -> Device -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
forall (io :: * -> *).
MonadIO io =>
Device -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyDevice Device
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)


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

-- | vkDestroyDevice - Destroy a logical device
--
-- = Description
--
-- To ensure that no work is active on the device,
-- 'Vulkan.Core10.Queue.deviceWaitIdle' /can/ be used to gate the
-- destruction of the device. Prior to destroying a device, an application
-- is responsible for destroying\/freeing any Vulkan objects that were
-- created using that device as the first parameter of the corresponding
-- @vkCreate*@ or @vkAllocate*@ command.
--
-- Note
--
-- The lifetime of each of these objects is bound by the lifetime of the
-- 'Vulkan.Core10.Handles.Device' object. Therefore, to avoid resource
-- leaks, it is critical that an application explicitly free all of these
-- resources prior to calling 'destroyDevice'.
--
-- == Valid Usage
--
-- -   All child objects created on @device@ /must/ have been destroyed
--     prior to destroying @device@
--
-- -   If 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @device@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   If no 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @device@ was created, @pAllocator@ /must/ be @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   If @device@ is not @NULL@, @device@ /must/ be a valid
--     'Vulkan.Core10.Handles.Device' handle
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- == Host Synchronization
--
-- -   Host access to @device@ /must/ be externally synchronized
--
-- -   Host access to all 'Vulkan.Core10.Handles.Queue' objects received
--     from @device@ /must/ be externally synchronized
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device'
destroyDevice :: forall io
               . (MonadIO io)
              => -- | @device@ is the logical device to destroy.
                 Device
              -> -- | @pAllocator@ controls host memory allocation as described in the
                 -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                 -- chapter.
                 ("allocator" ::: Maybe AllocationCallbacks)
              -> io ()
destroyDevice :: Device -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyDevice device :: Device
device allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDestroyDevicePtr :: FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyDevicePtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
pVkDestroyDevice (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyDevicePtr FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> FunPtr
     (Ptr Device_T
      -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> 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 vkDestroyDevice is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyDevice' :: Ptr Device_T -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyDevice' = FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Ptr Device_T
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyDevice FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyDevicePtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyDevice' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkDeviceQueueCreateInfo - Structure specifying parameters of a newly
-- created device queue
--
-- == Valid Usage
--
-- -   @queueFamilyIndex@ /must/ be less than @pQueueFamilyPropertyCount@
--     returned by
--     'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceQueueFamilyProperties'
--
-- -   @queueCount@ /must/ be less than or equal to the @queueCount@ member
--     of the 'Vulkan.Core10.DeviceInitialization.QueueFamilyProperties'
--     structure, as returned by
--     'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceQueueFamilyProperties'
--     in the @pQueueFamilyProperties@[queueFamilyIndex]
--
-- -   Each element of @pQueuePriorities@ /must/ be between @0.0@ and @1.0@
--     inclusive
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-protectedMemory protected memory>
--     feature is not enabled, the
--     'Vulkan.Core10.Enums.DeviceQueueCreateFlagBits.DEVICE_QUEUE_CREATE_PROTECTED_BIT'
--     bit of @flags@ /must/ not be set
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_QUEUE_CREATE_INFO'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_EXT_global_priority.DeviceQueueGlobalPriorityCreateInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.DeviceQueueCreateFlagBits.DeviceQueueCreateFlagBits'
--     values
--
-- -   @pQueuePriorities@ /must/ be a valid pointer to an array of
--     @queueCount@ @float@ values
--
-- -   @queueCount@ /must/ be greater than @0@
--
-- = See Also
--
-- 'DeviceCreateInfo',
-- 'Vulkan.Core10.Enums.DeviceQueueCreateFlagBits.DeviceQueueCreateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceQueueCreateInfo (es :: [Type]) = DeviceQueueCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    DeviceQueueCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is a bitmask indicating behavior of the queue.
    DeviceQueueCreateInfo es -> DeviceQueueCreateFlags
flags :: DeviceQueueCreateFlags
  , -- | @queueFamilyIndex@ is an unsigned integer indicating the index of the
    -- queue family to create on this device. This index corresponds to the
    -- index of an element of the @pQueueFamilyProperties@ array that was
    -- returned by
    -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceQueueFamilyProperties'.
    DeviceQueueCreateInfo es -> Word32
queueFamilyIndex :: Word32
  , -- | @pQueuePriorities@ is a pointer to an array of @queueCount@ normalized
    -- floating point values, specifying priorities of work that will be
    -- submitted to each created queue. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#devsandqueues-priority Queue Priority>
    -- for more information.
    DeviceQueueCreateInfo es -> Vector Float
queuePriorities :: Vector Float
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceQueueCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (DeviceQueueCreateInfo es)

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

instance (Extendss DeviceQueueCreateInfo es, PokeChain es) => ToCStruct (DeviceQueueCreateInfo es) where
  withCStruct :: DeviceQueueCreateInfo es
-> (Ptr (DeviceQueueCreateInfo es) -> IO b) -> IO b
withCStruct x :: DeviceQueueCreateInfo es
x f :: Ptr (DeviceQueueCreateInfo es) -> IO b
f = Int -> Int -> (Ptr (DeviceQueueCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr (DeviceQueueCreateInfo es) -> IO b) -> IO b)
-> (Ptr (DeviceQueueCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (DeviceQueueCreateInfo es)
p -> Ptr (DeviceQueueCreateInfo es)
-> DeviceQueueCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (DeviceQueueCreateInfo es)
p DeviceQueueCreateInfo es
x (Ptr (DeviceQueueCreateInfo es) -> IO b
f Ptr (DeviceQueueCreateInfo es)
p)
  pokeCStruct :: Ptr (DeviceQueueCreateInfo es)
-> DeviceQueueCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (DeviceQueueCreateInfo es)
p DeviceQueueCreateInfo{..} 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 (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_QUEUE_CREATE_INFO)
    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 (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo 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 DeviceQueueCreateFlags -> DeviceQueueCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr DeviceQueueCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceQueueCreateFlags)) (DeviceQueueCreateFlags
flags)
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
queueFamilyIndex)
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Float -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Float -> Int) -> Vector Float -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Float
queuePriorities)) :: Word32))
    Ptr CFloat
pPQueuePriorities' <- ((Ptr CFloat -> IO b) -> IO b) -> ContT b IO (Ptr CFloat)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CFloat -> IO b) -> IO b) -> ContT b IO (Ptr CFloat))
-> ((Ptr CFloat -> IO b) -> IO b) -> ContT b IO (Ptr CFloat)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr CFloat -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @CFloat ((Vector Float -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Float
queuePriorities)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> Float -> IO ()) -> Vector Float -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Float
e -> Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pPQueuePriorities' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e))) (Vector Float
queuePriorities)
    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 CFloat) -> Ptr CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr (Ptr CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CFloat))) (Ptr CFloat
pPQueuePriorities')
    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 (DeviceQueueCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (DeviceQueueCreateInfo 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 (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_QUEUE_CREATE_INFO)
    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 (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo 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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    Ptr CFloat
pPQueuePriorities' <- ((Ptr CFloat -> IO b) -> IO b) -> ContT b IO (Ptr CFloat)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CFloat -> IO b) -> IO b) -> ContT b IO (Ptr CFloat))
-> ((Ptr CFloat -> IO b) -> IO b) -> ContT b IO (Ptr CFloat)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr CFloat -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @CFloat ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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
$ (Int -> Float -> IO ()) -> Vector Float -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Float
e -> Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pPQueuePriorities' Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e))) (Vector Float
forall a. Monoid a => a
mempty)
    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 CFloat) -> Ptr CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr (Ptr CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CFloat))) (Ptr CFloat
pPQueuePriorities')
    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 DeviceQueueCreateInfo es, PeekChain es) => FromCStruct (DeviceQueueCreateInfo es) where
  peekCStruct :: Ptr (DeviceQueueCreateInfo es) -> IO (DeviceQueueCreateInfo es)
peekCStruct p :: Ptr (DeviceQueueCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo 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)
    DeviceQueueCreateFlags
flags <- Ptr DeviceQueueCreateFlags -> IO DeviceQueueCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @DeviceQueueCreateFlags ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr DeviceQueueCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceQueueCreateFlags))
    Word32
queueFamilyIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Word32
queueCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    Ptr CFloat
pQueuePriorities <- Ptr (Ptr CFloat) -> IO (Ptr CFloat)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr CFloat) ((Ptr (DeviceQueueCreateInfo es)
p Ptr (DeviceQueueCreateInfo es) -> Int -> Ptr (Ptr CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr CFloat)))
    Vector Float
pQueuePriorities' <- Int -> (Int -> IO Float) -> IO (Vector Float)
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
queueCount) (\i :: Int
i -> do
      CFloat
pQueuePrioritiesElem <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pQueuePriorities Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr CFloat))
      Float -> IO Float
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Float -> IO Float) -> Float -> IO Float
forall a b. (a -> b) -> a -> b
$ (\(CFloat a :: Float
a) -> Float
a) CFloat
pQueuePrioritiesElem)
    DeviceQueueCreateInfo es -> IO (DeviceQueueCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceQueueCreateInfo es -> IO (DeviceQueueCreateInfo es))
-> DeviceQueueCreateInfo es -> IO (DeviceQueueCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> DeviceQueueCreateFlags
-> Word32
-> Vector Float
-> DeviceQueueCreateInfo es
forall (es :: [*]).
Chain es
-> DeviceQueueCreateFlags
-> Word32
-> Vector Float
-> DeviceQueueCreateInfo es
DeviceQueueCreateInfo
             Chain es
next DeviceQueueCreateFlags
flags Word32
queueFamilyIndex Vector Float
pQueuePriorities'

instance es ~ '[] => Zero (DeviceQueueCreateInfo es) where
  zero :: DeviceQueueCreateInfo es
zero = Chain es
-> DeviceQueueCreateFlags
-> Word32
-> Vector Float
-> DeviceQueueCreateInfo es
forall (es :: [*]).
Chain es
-> DeviceQueueCreateFlags
-> Word32
-> Vector Float
-> DeviceQueueCreateInfo es
DeviceQueueCreateInfo
           ()
           DeviceQueueCreateFlags
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero
           Vector Float
forall a. Monoid a => a
mempty


-- | VkDeviceCreateInfo - Structure specifying parameters of a newly created
-- device
--
-- == Valid Usage
--
-- -   The @queueFamilyIndex@ member of each element of @pQueueCreateInfos@
--     /must/ be unique within @pQueueCreateInfos@, except that two members
--     can share the same @queueFamilyIndex@ if one is a protected-capable
--     queue and one is not a protected-capable queue
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
--     structure, then @pEnabledFeatures@ /must/ be @NULL@
--
-- -   @ppEnabledExtensionNames@ /must/ not contain
--     @VK_AMD_negative_viewport_height@
--
-- -   @ppEnabledExtensionNames@ /must/ not contain both
--     @VK_KHR_buffer_device_address@ and @VK_EXT_buffer_device_address@
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core12.PhysicalDeviceVulkan11Features' structure, then it
--     /must/ not include a
--     'Vulkan.Core11.Promoted_From_VK_KHR_16bit_storage.PhysicalDevice16BitStorageFeatures',
--     'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewFeatures',
--     'Vulkan.Core11.Promoted_From_VK_KHR_variable_pointers.PhysicalDeviceVariablePointersFeatures',
--     'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.PhysicalDeviceProtectedMemoryFeatures',
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.PhysicalDeviceSamplerYcbcrConversionFeatures',
--     or
--     'Vulkan.Core11.Promoted_From_VK_KHR_shader_draw_parameters.PhysicalDeviceShaderDrawParametersFeatures'
--     structure
--
-- -   If the @pNext@ chain includes a
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features' structure, then it
--     /must/ not include a
--     'Vulkan.Core12.Promoted_From_VK_KHR_8bit_storage.PhysicalDevice8BitStorageFeatures',
--     'Vulkan.Core12.Promoted_From_VK_KHR_shader_atomic_int64.PhysicalDeviceShaderAtomicInt64Features',
--     'Vulkan.Core12.Promoted_From_VK_KHR_shader_float16_int8.PhysicalDeviceShaderFloat16Int8Features',
--     'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingFeatures',
--     'Vulkan.Core12.Promoted_From_VK_EXT_scalar_block_layout.PhysicalDeviceScalarBlockLayoutFeatures',
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.PhysicalDeviceImagelessFramebufferFeatures',
--     'Vulkan.Core12.Promoted_From_VK_KHR_uniform_buffer_standard_layout.PhysicalDeviceUniformBufferStandardLayoutFeatures',
--     'Vulkan.Core12.Promoted_From_VK_KHR_shader_subgroup_extended_types.PhysicalDeviceShaderSubgroupExtendedTypesFeatures',
--     'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.PhysicalDeviceSeparateDepthStencilLayoutsFeatures',
--     'Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset.PhysicalDeviceHostQueryResetFeatures',
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.PhysicalDeviceTimelineSemaphoreFeatures',
--     'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.PhysicalDeviceBufferDeviceAddressFeatures',
--     or
--     'Vulkan.Core12.Promoted_From_VK_KHR_vulkan_memory_model.PhysicalDeviceVulkanMemoryModelFeatures'
--     structure
--
-- -   If @ppEnabledExtensions@ contains @\"VK_KHR_draw_indirect_count\"@
--     and the @pNext@ chain includes a
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features' structure, then
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features'::@drawIndirectCount@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   If @ppEnabledExtensions@ contains
--     @\"VK_KHR_sampler_mirror_clamp_to_edge\"@ and the @pNext@ chain
--     includes a 'Vulkan.Core12.PhysicalDeviceVulkan12Features' structure,
--     then
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features'::@samplerMirrorClampToEdge@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   If @ppEnabledExtensions@ contains @\"VK_EXT_descriptor_indexing\"@
--     and the @pNext@ chain includes a
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features' structure, then
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features'::@descriptorIndexing@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   If @ppEnabledExtensions@ contains @\"VK_EXT_sampler_filter_minmax\"@
--     and the @pNext@ chain includes a
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features' structure, then
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features'::@samplerFilterMinmax@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   If @ppEnabledExtensions@ contains
--     @\"VK_EXT_shader_viewport_index_layer\"@ and the @pNext@ chain
--     includes a 'Vulkan.Core12.PhysicalDeviceVulkan12Features' structure,
--     then
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features'::@shaderOutputViewportIndex@
--     and
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features'::@shaderOutputLayer@
--     /must/ both be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_CREATE_INFO'
--
-- -   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_NV_device_diagnostics_config.DeviceDiagnosticsConfigCreateInfoNV',
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group_creation.DeviceGroupDeviceCreateInfo',
--     'Vulkan.Extensions.VK_AMD_memory_overallocation_behavior.DeviceMemoryOverallocationCreateInfoAMD',
--     'Vulkan.Extensions.VK_EXT_private_data.DevicePrivateDataCreateInfoEXT',
--     'Vulkan.Core11.Promoted_From_VK_KHR_16bit_storage.PhysicalDevice16BitStorageFeatures',
--     'Vulkan.Extensions.VK_EXT_4444_formats.PhysicalDevice4444FormatsFeaturesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_8bit_storage.PhysicalDevice8BitStorageFeatures',
--     'Vulkan.Extensions.VK_EXT_astc_decode_mode.PhysicalDeviceASTCDecodeFeaturesEXT',
--     'Vulkan.Extensions.VK_EXT_blend_operation_advanced.PhysicalDeviceBlendOperationAdvancedFeaturesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.PhysicalDeviceBufferDeviceAddressFeatures',
--     'Vulkan.Extensions.VK_EXT_buffer_device_address.PhysicalDeviceBufferDeviceAddressFeaturesEXT',
--     'Vulkan.Extensions.VK_AMD_device_coherent_memory.PhysicalDeviceCoherentMemoryFeaturesAMD',
--     'Vulkan.Extensions.VK_NV_compute_shader_derivatives.PhysicalDeviceComputeShaderDerivativesFeaturesNV',
--     'Vulkan.Extensions.VK_EXT_conditional_rendering.PhysicalDeviceConditionalRenderingFeaturesEXT',
--     'Vulkan.Extensions.VK_NV_cooperative_matrix.PhysicalDeviceCooperativeMatrixFeaturesNV',
--     'Vulkan.Extensions.VK_NV_corner_sampled_image.PhysicalDeviceCornerSampledImageFeaturesNV',
--     'Vulkan.Extensions.VK_NV_coverage_reduction_mode.PhysicalDeviceCoverageReductionModeFeaturesNV',
--     'Vulkan.Extensions.VK_EXT_custom_border_color.PhysicalDeviceCustomBorderColorFeaturesEXT',
--     'Vulkan.Extensions.VK_NV_dedicated_allocation_image_aliasing.PhysicalDeviceDedicatedAllocationImageAliasingFeaturesNV',
--     'Vulkan.Extensions.VK_EXT_depth_clip_enable.PhysicalDeviceDepthClipEnableFeaturesEXT',
--     'Vulkan.Core12.Promoted_From_VK_EXT_descriptor_indexing.PhysicalDeviceDescriptorIndexingFeatures',
--     'Vulkan.Extensions.VK_NV_device_generated_commands.PhysicalDeviceDeviceGeneratedCommandsFeaturesNV',
--     'Vulkan.Extensions.VK_NV_device_diagnostics_config.PhysicalDeviceDiagnosticsConfigFeaturesNV',
--     'Vulkan.Extensions.VK_NV_scissor_exclusive.PhysicalDeviceExclusiveScissorFeaturesNV',
--     'Vulkan.Extensions.VK_EXT_extended_dynamic_state.PhysicalDeviceExtendedDynamicStateFeaturesEXT',
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Extensions.VK_EXT_fragment_density_map2.PhysicalDeviceFragmentDensityMap2FeaturesEXT',
--     'Vulkan.Extensions.VK_EXT_fragment_density_map.PhysicalDeviceFragmentDensityMapFeaturesEXT',
--     'Vulkan.Extensions.VK_NV_fragment_shader_barycentric.PhysicalDeviceFragmentShaderBarycentricFeaturesNV',
--     'Vulkan.Extensions.VK_EXT_fragment_shader_interlock.PhysicalDeviceFragmentShaderInterlockFeaturesEXT',
--     'Vulkan.Core12.Promoted_From_VK_EXT_host_query_reset.PhysicalDeviceHostQueryResetFeatures',
--     'Vulkan.Extensions.VK_EXT_image_robustness.PhysicalDeviceImageRobustnessFeaturesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_imageless_framebuffer.PhysicalDeviceImagelessFramebufferFeatures',
--     'Vulkan.Extensions.VK_EXT_index_type_uint8.PhysicalDeviceIndexTypeUint8FeaturesEXT',
--     'Vulkan.Extensions.VK_EXT_inline_uniform_block.PhysicalDeviceInlineUniformBlockFeaturesEXT',
--     'Vulkan.Extensions.VK_EXT_line_rasterization.PhysicalDeviceLineRasterizationFeaturesEXT',
--     'Vulkan.Extensions.VK_EXT_memory_priority.PhysicalDeviceMemoryPriorityFeaturesEXT',
--     'Vulkan.Extensions.VK_NV_mesh_shader.PhysicalDeviceMeshShaderFeaturesNV',
--     'Vulkan.Core11.Promoted_From_VK_KHR_multiview.PhysicalDeviceMultiviewFeatures',
--     'Vulkan.Extensions.VK_KHR_performance_query.PhysicalDevicePerformanceQueryFeaturesKHR',
--     'Vulkan.Extensions.VK_EXT_pipeline_creation_cache_control.PhysicalDevicePipelineCreationCacheControlFeaturesEXT',
--     'Vulkan.Extensions.VK_KHR_pipeline_executable_properties.PhysicalDevicePipelineExecutablePropertiesFeaturesKHR',
--     'Vulkan.Extensions.VK_EXT_private_data.PhysicalDevicePrivateDataFeaturesEXT',
--     'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.PhysicalDeviceProtectedMemoryFeatures',
--     'Vulkan.Extensions.VK_KHR_ray_tracing.PhysicalDeviceRayTracingFeaturesKHR',
--     'Vulkan.Extensions.VK_NV_representative_fragment_test.PhysicalDeviceRepresentativeFragmentTestFeaturesNV',
--     'Vulkan.Extensions.VK_EXT_robustness2.PhysicalDeviceRobustness2FeaturesEXT',
--     'Vulkan.Core11.Promoted_From_VK_KHR_sampler_ycbcr_conversion.PhysicalDeviceSamplerYcbcrConversionFeatures',
--     'Vulkan.Core12.Promoted_From_VK_EXT_scalar_block_layout.PhysicalDeviceScalarBlockLayoutFeatures',
--     'Vulkan.Core12.Promoted_From_VK_KHR_separate_depth_stencil_layouts.PhysicalDeviceSeparateDepthStencilLayoutsFeatures',
--     'Vulkan.Extensions.VK_EXT_shader_atomic_float.PhysicalDeviceShaderAtomicFloatFeaturesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_shader_atomic_int64.PhysicalDeviceShaderAtomicInt64Features',
--     'Vulkan.Extensions.VK_KHR_shader_clock.PhysicalDeviceShaderClockFeaturesKHR',
--     'Vulkan.Extensions.VK_EXT_shader_demote_to_helper_invocation.PhysicalDeviceShaderDemoteToHelperInvocationFeaturesEXT',
--     'Vulkan.Core11.Promoted_From_VK_KHR_shader_draw_parameters.PhysicalDeviceShaderDrawParametersFeatures',
--     'Vulkan.Core12.Promoted_From_VK_KHR_shader_float16_int8.PhysicalDeviceShaderFloat16Int8Features',
--     'Vulkan.Extensions.VK_NV_shader_image_footprint.PhysicalDeviceShaderImageFootprintFeaturesNV',
--     'Vulkan.Extensions.VK_INTEL_shader_integer_functions2.PhysicalDeviceShaderIntegerFunctions2FeaturesINTEL',
--     'Vulkan.Extensions.VK_NV_shader_sm_builtins.PhysicalDeviceShaderSMBuiltinsFeaturesNV',
--     'Vulkan.Core12.Promoted_From_VK_KHR_shader_subgroup_extended_types.PhysicalDeviceShaderSubgroupExtendedTypesFeatures',
--     'Vulkan.Extensions.VK_NV_shading_rate_image.PhysicalDeviceShadingRateImageFeaturesNV',
--     'Vulkan.Extensions.VK_EXT_subgroup_size_control.PhysicalDeviceSubgroupSizeControlFeaturesEXT',
--     'Vulkan.Extensions.VK_EXT_texel_buffer_alignment.PhysicalDeviceTexelBufferAlignmentFeaturesEXT',
--     'Vulkan.Extensions.VK_EXT_texture_compression_astc_hdr.PhysicalDeviceTextureCompressionASTCHDRFeaturesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.PhysicalDeviceTimelineSemaphoreFeatures',
--     'Vulkan.Extensions.VK_EXT_transform_feedback.PhysicalDeviceTransformFeedbackFeaturesEXT',
--     'Vulkan.Core12.Promoted_From_VK_KHR_uniform_buffer_standard_layout.PhysicalDeviceUniformBufferStandardLayoutFeatures',
--     'Vulkan.Core11.Promoted_From_VK_KHR_variable_pointers.PhysicalDeviceVariablePointersFeatures',
--     'Vulkan.Extensions.VK_EXT_vertex_attribute_divisor.PhysicalDeviceVertexAttributeDivisorFeaturesEXT',
--     'Vulkan.Core12.PhysicalDeviceVulkan11Features',
--     'Vulkan.Core12.PhysicalDeviceVulkan12Features',
--     'Vulkan.Core12.Promoted_From_VK_KHR_vulkan_memory_model.PhysicalDeviceVulkanMemoryModelFeatures',
--     or
--     'Vulkan.Extensions.VK_EXT_ycbcr_image_arrays.PhysicalDeviceYcbcrImageArraysFeaturesEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique, with the exception of structures of type
--     'Vulkan.Extensions.VK_EXT_private_data.DevicePrivateDataCreateInfoEXT'
--
-- -   @flags@ /must/ be @0@
--
-- -   @pQueueCreateInfos@ /must/ be a valid pointer to an array of
--     @queueCreateInfoCount@ valid 'DeviceQueueCreateInfo' structures
--
-- -   If @enabledLayerCount@ is not @0@, @ppEnabledLayerNames@ /must/ be a
--     valid pointer to an array of @enabledLayerCount@ null-terminated
--     UTF-8 strings
--
-- -   If @enabledExtensionCount@ is not @0@, @ppEnabledExtensionNames@
--     /must/ be a valid pointer to an array of @enabledExtensionCount@
--     null-terminated UTF-8 strings
--
-- -   If @pEnabledFeatures@ is not @NULL@, @pEnabledFeatures@ /must/ be a
--     valid pointer to a valid
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceFeatures'
--     structure
--
-- -   @queueCreateInfoCount@ /must/ be greater than @0@
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.DeviceCreateFlags.DeviceCreateFlags',
-- 'DeviceQueueCreateInfo',
-- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceFeatures',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'createDevice'
data DeviceCreateInfo (es :: [Type]) = DeviceCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    DeviceCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is reserved for future use.
    DeviceCreateInfo es -> DeviceCreateFlags
flags :: DeviceCreateFlags
  , -- | @pQueueCreateInfos@ is a pointer to an array of 'DeviceQueueCreateInfo'
    -- structures describing the queues that are requested to be created along
    -- with the logical device. Refer to the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#devsandqueues-queue-creation Queue Creation>
    -- section below for further details.
    DeviceCreateInfo es -> Vector (SomeStruct DeviceQueueCreateInfo)
queueCreateInfos :: Vector (SomeStruct DeviceQueueCreateInfo)
  , -- | @ppEnabledLayerNames@ is deprecated and ignored. See
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-layers-devicelayerdeprecation>.
    DeviceCreateInfo es -> Vector ByteString
enabledLayerNames :: Vector ByteString
  , -- | @ppEnabledExtensionNames@ is a pointer to an array of
    -- @enabledExtensionCount@ null-terminated UTF-8 strings containing the
    -- names of extensions to enable for the created device. See the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-extensions>
    -- section for further details.
    DeviceCreateInfo es -> Vector ByteString
enabledExtensionNames :: Vector ByteString
  , -- | @pEnabledFeatures@ is @NULL@ or a pointer to a
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceFeatures' structure
    -- containing boolean indicators of all the features to be enabled. Refer
    -- to the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features Features>
    -- section for further details.
    DeviceCreateInfo es -> Maybe PhysicalDeviceFeatures
enabledFeatures :: Maybe PhysicalDeviceFeatures
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (DeviceCreateInfo es)

instance Extensible DeviceCreateInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_DEVICE_CREATE_INFO
  setNext :: DeviceCreateInfo ds -> Chain es -> DeviceCreateInfo es
setNext x :: DeviceCreateInfo ds
x next :: Chain es
next = DeviceCreateInfo ds
x{$sel:next:DeviceCreateInfo :: Chain es
next = Chain es
next}
  getNext :: DeviceCreateInfo es -> Chain es
getNext DeviceCreateInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends DeviceCreateInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends DeviceCreateInfo e => b) -> Maybe b
extends _ f :: Extends DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable DeviceDiagnosticsConfigCreateInfoNV) =>
Maybe (e :~: DeviceDiagnosticsConfigCreateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeviceDiagnosticsConfigCreateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable DeviceMemoryOverallocationCreateInfoAMD) =>
Maybe (e :~: DeviceMemoryOverallocationCreateInfoAMD)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeviceMemoryOverallocationCreateInfoAMD = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable DeviceGroupDeviceCreateInfo) =>
Maybe (e :~: DeviceGroupDeviceCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeviceGroupDeviceCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends DeviceCreateInfo 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 DeviceCreateInfo 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 DeviceCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable (PhysicalDeviceFeatures2 '[])) =>
Maybe (e :~: PhysicalDeviceFeatures2 '[])
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @(PhysicalDeviceFeatures2 '[]) = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends DeviceCreateInfo 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 DeviceCreateInfo e => b
f
    | Just Refl <- (Typeable e, Typeable DevicePrivateDataCreateInfoEXT) =>
Maybe (e :~: DevicePrivateDataCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DevicePrivateDataCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends DeviceCreateInfo 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 DeviceCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss DeviceCreateInfo es, PokeChain es) => ToCStruct (DeviceCreateInfo es) where
  withCStruct :: DeviceCreateInfo es -> (Ptr (DeviceCreateInfo es) -> IO b) -> IO b
withCStruct x :: DeviceCreateInfo es
x f :: Ptr (DeviceCreateInfo es) -> IO b
f = Int -> Int -> (Ptr (DeviceCreateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 72 8 ((Ptr (DeviceCreateInfo es) -> IO b) -> IO b)
-> (Ptr (DeviceCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (DeviceCreateInfo es)
p -> Ptr (DeviceCreateInfo es) -> DeviceCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (DeviceCreateInfo es)
p DeviceCreateInfo es
x (Ptr (DeviceCreateInfo es) -> IO b
f Ptr (DeviceCreateInfo es)
p)
  pokeCStruct :: Ptr (DeviceCreateInfo es) -> DeviceCreateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (DeviceCreateInfo es)
p DeviceCreateInfo{..} 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 (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_CREATE_INFO)
    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 (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo 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 DeviceCreateFlags -> DeviceCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr DeviceCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceCreateFlags)) (DeviceCreateFlags
flags)
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector (SomeStruct DeviceQueueCreateInfo) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct DeviceQueueCreateInfo) -> Int)
-> Vector (SomeStruct DeviceQueueCreateInfo) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct DeviceQueueCreateInfo)
queueCreateInfos)) :: Word32))
    Ptr (DeviceQueueCreateInfo Any)
pPQueueCreateInfos' <- ((Ptr (DeviceQueueCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (DeviceQueueCreateInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (DeviceQueueCreateInfo Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (DeviceQueueCreateInfo Any)))
-> ((Ptr (DeviceQueueCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (DeviceQueueCreateInfo Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (DeviceQueueCreateInfo Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(DeviceQueueCreateInfo _) ((Vector (SomeStruct DeviceQueueCreateInfo) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct DeviceQueueCreateInfo)
queueCreateInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
    (Int -> SomeStruct DeviceQueueCreateInfo -> ContT b IO ())
-> Vector (SomeStruct DeviceQueueCreateInfo) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct DeviceQueueCreateInfo
e -> ((() -> 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 (SomeStruct DeviceQueueCreateInfo)
-> SomeStruct DeviceQueueCreateInfo -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (DeviceQueueCreateInfo Any)
-> Ptr (SomeStruct DeviceQueueCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (DeviceQueueCreateInfo Any)
pPQueueCreateInfos' Ptr (DeviceQueueCreateInfo Any)
-> Int -> Ptr (DeviceQueueCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (DeviceQueueCreateInfo _))) (SomeStruct DeviceQueueCreateInfo
e) (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
$ ())) (Vector (SomeStruct DeviceQueueCreateInfo)
queueCreateInfos)
    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 (DeviceQueueCreateInfo Any))
-> Ptr (DeviceQueueCreateInfo Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es)
-> Int -> Ptr (Ptr (DeviceQueueCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (DeviceQueueCreateInfo _)))) (Ptr (DeviceQueueCreateInfo Any)
pPQueueCreateInfos')
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ByteString -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ByteString -> Int) -> Vector ByteString -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ByteString
enabledLayerNames)) :: Word32))
    Ptr (Ptr CChar)
pPpEnabledLayerNames' <- ((Ptr (Ptr CChar) -> IO b) -> IO b) -> ContT b IO (Ptr (Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO (Ptr (Ptr CChar)))
-> ((Ptr (Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr CChar))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (Ptr CChar) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CChar) ((Vector ByteString -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ByteString
enabledLayerNames)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    (Int -> ByteString -> ContT b IO ())
-> Vector ByteString -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ByteString
e -> do
      Ptr CChar
ppEnabledLayerNames'' <- ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar))
-> ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ByteString -> (Ptr CChar -> IO b) -> IO b
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
useAsCString (ByteString
e)
      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 CChar) -> Ptr CChar -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr (Ptr CChar)
pPpEnabledLayerNames' Ptr (Ptr CChar) -> Int -> Ptr (Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar)) Ptr CChar
ppEnabledLayerNames'') (Vector ByteString
enabledLayerNames)
    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 CChar)) -> Ptr (Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr (Ptr (Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (Ptr CChar)))) (Ptr (Ptr CChar)
pPpEnabledLayerNames')
    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 Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ((Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ByteString -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ByteString -> Int) -> Vector ByteString -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ByteString
enabledExtensionNames)) :: Word32))
    Ptr (Ptr CChar)
pPpEnabledExtensionNames' <- ((Ptr (Ptr CChar) -> IO b) -> IO b) -> ContT b IO (Ptr (Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO (Ptr (Ptr CChar)))
-> ((Ptr (Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr CChar))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (Ptr CChar) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CChar) ((Vector ByteString -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ByteString
enabledExtensionNames)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    (Int -> ByteString -> ContT b IO ())
-> Vector ByteString -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ByteString
e -> do
      Ptr CChar
ppEnabledExtensionNames'' <- ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar))
-> ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ByteString -> (Ptr CChar -> IO b) -> IO b
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
useAsCString (ByteString
e)
      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 CChar) -> Ptr CChar -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr (Ptr CChar)
pPpEnabledExtensionNames' Ptr (Ptr CChar) -> Int -> Ptr (Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar)) Ptr CChar
ppEnabledExtensionNames'') (Vector ByteString
enabledExtensionNames)
    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 CChar)) -> Ptr (Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr (Ptr (Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (Ptr CChar)))) (Ptr (Ptr CChar)
pPpEnabledExtensionNames')
    Ptr PhysicalDeviceFeatures
pEnabledFeatures'' <- case (Maybe PhysicalDeviceFeatures
enabledFeatures) of
      Nothing -> Ptr PhysicalDeviceFeatures
-> ContT b IO (Ptr PhysicalDeviceFeatures)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr PhysicalDeviceFeatures
forall a. Ptr a
nullPtr
      Just j :: PhysicalDeviceFeatures
j -> ((Ptr PhysicalDeviceFeatures -> IO b) -> IO b)
-> ContT b IO (Ptr PhysicalDeviceFeatures)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PhysicalDeviceFeatures -> IO b) -> IO b)
 -> ContT b IO (Ptr PhysicalDeviceFeatures))
-> ((Ptr PhysicalDeviceFeatures -> IO b) -> IO b)
-> ContT b IO (Ptr PhysicalDeviceFeatures)
forall a b. (a -> b) -> a -> b
$ PhysicalDeviceFeatures
-> (Ptr PhysicalDeviceFeatures -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PhysicalDeviceFeatures
j)
    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 PhysicalDeviceFeatures)
-> Ptr PhysicalDeviceFeatures -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es)
-> Int -> Ptr (Ptr PhysicalDeviceFeatures)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr PhysicalDeviceFeatures))) Ptr PhysicalDeviceFeatures
pEnabledFeatures''
    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 = 72
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (DeviceCreateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (DeviceCreateInfo 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 (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_CREATE_INFO)
    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 (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    Ptr (DeviceQueueCreateInfo Any)
pPQueueCreateInfos' <- ((Ptr (DeviceQueueCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (DeviceQueueCreateInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (DeviceQueueCreateInfo Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (DeviceQueueCreateInfo Any)))
-> ((Ptr (DeviceQueueCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (DeviceQueueCreateInfo Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (DeviceQueueCreateInfo Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(DeviceQueueCreateInfo _) ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
    (Int -> SomeStruct DeviceQueueCreateInfo -> ContT b IO ())
-> Vector (SomeStruct DeviceQueueCreateInfo) -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct DeviceQueueCreateInfo
e -> ((() -> 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 (SomeStruct DeviceQueueCreateInfo)
-> SomeStruct DeviceQueueCreateInfo -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (DeviceQueueCreateInfo Any)
-> Ptr (SomeStruct DeviceQueueCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (DeviceQueueCreateInfo Any)
pPQueueCreateInfos' Ptr (DeviceQueueCreateInfo Any)
-> Int -> Ptr (DeviceQueueCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (DeviceQueueCreateInfo _))) (SomeStruct DeviceQueueCreateInfo
e) (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
$ ())) (Vector (SomeStruct DeviceQueueCreateInfo)
forall a. Monoid a => a
mempty)
    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 (DeviceQueueCreateInfo Any))
-> Ptr (DeviceQueueCreateInfo Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es)
-> Int -> Ptr (Ptr (DeviceQueueCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (DeviceQueueCreateInfo _)))) (Ptr (DeviceQueueCreateInfo Any)
pPQueueCreateInfos')
    Ptr (Ptr CChar)
pPpEnabledLayerNames' <- ((Ptr (Ptr CChar) -> IO b) -> IO b) -> ContT b IO (Ptr (Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO (Ptr (Ptr CChar)))
-> ((Ptr (Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr CChar))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (Ptr CChar) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CChar) ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    (Int -> ByteString -> ContT b IO ())
-> Vector ByteString -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ByteString
e -> do
      Ptr CChar
ppEnabledLayerNames'' <- ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar))
-> ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ByteString -> (Ptr CChar -> IO b) -> IO b
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
useAsCString (ByteString
e)
      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 CChar) -> Ptr CChar -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr (Ptr CChar)
pPpEnabledLayerNames' Ptr (Ptr CChar) -> Int -> Ptr (Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar)) Ptr CChar
ppEnabledLayerNames'') (Vector ByteString
forall a. Monoid a => a
mempty)
    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 CChar)) -> Ptr (Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr (Ptr (Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (Ptr CChar)))) (Ptr (Ptr CChar)
pPpEnabledLayerNames')
    Ptr (Ptr CChar)
pPpEnabledExtensionNames' <- ((Ptr (Ptr CChar) -> IO b) -> IO b) -> ContT b IO (Ptr (Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Ptr CChar) -> IO b) -> IO b)
 -> ContT b IO (Ptr (Ptr CChar)))
-> ((Ptr (Ptr CChar) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr CChar))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (Ptr CChar) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CChar) ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    (Int -> ByteString -> ContT b IO ())
-> Vector ByteString -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: ByteString
e -> do
      Ptr CChar
ppEnabledExtensionNames'' <- ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar))
-> ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ByteString -> (Ptr CChar -> IO b) -> IO b
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
useAsCString (ByteString
e)
      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 CChar) -> Ptr CChar -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr (Ptr CChar)
pPpEnabledExtensionNames' Ptr (Ptr CChar) -> Int -> Ptr (Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar)) Ptr CChar
ppEnabledExtensionNames'') (Vector ByteString
forall a. Monoid a => a
mempty)
    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 CChar)) -> Ptr (Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr (Ptr (Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (Ptr CChar)))) (Ptr (Ptr CChar)
pPpEnabledExtensionNames')
    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 DeviceCreateInfo es, PeekChain es) => FromCStruct (DeviceCreateInfo es) where
  peekCStruct :: Ptr (DeviceCreateInfo es) -> IO (DeviceCreateInfo es)
peekCStruct p :: Ptr (DeviceCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo 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)
    DeviceCreateFlags
flags <- Ptr DeviceCreateFlags -> IO DeviceCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @DeviceCreateFlags ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr DeviceCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceCreateFlags))
    Word32
queueCreateInfoCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr (DeviceQueueCreateInfo Any)
pQueueCreateInfos <- Ptr (Ptr (DeviceQueueCreateInfo Any))
-> IO (Ptr (DeviceQueueCreateInfo Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (DeviceQueueCreateInfo _)) ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es)
-> Int -> Ptr (Ptr (DeviceQueueCreateInfo a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (DeviceQueueCreateInfo a))))
    Vector (SomeStruct DeviceQueueCreateInfo)
pQueueCreateInfos' <- Int
-> (Int -> IO (SomeStruct DeviceQueueCreateInfo))
-> IO (Vector (SomeStruct DeviceQueueCreateInfo))
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
queueCreateInfoCount) (\i :: Int
i -> Ptr (SomeStruct DeviceQueueCreateInfo)
-> IO (SomeStruct DeviceQueueCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (DeviceQueueCreateInfo Any)
-> Ptr (SomeStruct DeviceQueueCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (DeviceQueueCreateInfo Any)
pQueueCreateInfos Ptr (DeviceQueueCreateInfo Any)
-> Int -> Ptr (DeviceQueueCreateInfo Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (DeviceQueueCreateInfo _)))))
    Word32
enabledLayerCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr (Ptr CChar)
ppEnabledLayerNames <- Ptr (Ptr (Ptr CChar)) -> IO (Ptr (Ptr CChar))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (Ptr CChar)) ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr (Ptr (Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr (Ptr CChar))))
    Vector ByteString
ppEnabledLayerNames' <- Int -> (Int -> IO ByteString) -> IO (Vector ByteString)
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
enabledLayerCount) (\i :: Int
i -> Ptr CChar -> IO ByteString
packCString (Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr CChar) -> IO (Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek ((Ptr (Ptr CChar)
ppEnabledLayerNames Ptr (Ptr CChar) -> Int -> Ptr (Ptr CChar)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar))))
    Word32
enabledExtensionCount <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    Ptr (Ptr CChar)
ppEnabledExtensionNames <- Ptr (Ptr (Ptr CChar)) -> IO (Ptr (Ptr CChar))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (Ptr CChar)) ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es) -> Int -> Ptr (Ptr (Ptr CChar))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (Ptr CChar))))
    Vector ByteString
ppEnabledExtensionNames' <- Int -> (Int -> IO ByteString) -> IO (Vector ByteString)
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
enabledExtensionCount) (\i :: Int
i -> Ptr CChar -> IO ByteString
packCString (Ptr CChar -> IO ByteString) -> IO (Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr (Ptr CChar) -> IO (Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek ((Ptr (Ptr CChar)
ppEnabledExtensionNames Ptr (Ptr CChar) -> Int -> Ptr (Ptr CChar)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CChar))))
    Ptr PhysicalDeviceFeatures
pEnabledFeatures <- Ptr (Ptr PhysicalDeviceFeatures) -> IO (Ptr PhysicalDeviceFeatures)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PhysicalDeviceFeatures) ((Ptr (DeviceCreateInfo es)
p Ptr (DeviceCreateInfo es)
-> Int -> Ptr (Ptr PhysicalDeviceFeatures)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr PhysicalDeviceFeatures)))
    Maybe PhysicalDeviceFeatures
pEnabledFeatures' <- (Ptr PhysicalDeviceFeatures -> IO PhysicalDeviceFeatures)
-> Ptr PhysicalDeviceFeatures -> IO (Maybe PhysicalDeviceFeatures)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr PhysicalDeviceFeatures
j -> Ptr PhysicalDeviceFeatures -> IO PhysicalDeviceFeatures
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PhysicalDeviceFeatures (Ptr PhysicalDeviceFeatures
j)) Ptr PhysicalDeviceFeatures
pEnabledFeatures
    DeviceCreateInfo es -> IO (DeviceCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceCreateInfo es -> IO (DeviceCreateInfo es))
-> DeviceCreateInfo es -> IO (DeviceCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> DeviceCreateFlags
-> Vector (SomeStruct DeviceQueueCreateInfo)
-> Vector ByteString
-> Vector ByteString
-> Maybe PhysicalDeviceFeatures
-> DeviceCreateInfo es
forall (es :: [*]).
Chain es
-> DeviceCreateFlags
-> Vector (SomeStruct DeviceQueueCreateInfo)
-> Vector ByteString
-> Vector ByteString
-> Maybe PhysicalDeviceFeatures
-> DeviceCreateInfo es
DeviceCreateInfo
             Chain es
next DeviceCreateFlags
flags Vector (SomeStruct DeviceQueueCreateInfo)
pQueueCreateInfos' Vector ByteString
ppEnabledLayerNames' Vector ByteString
ppEnabledExtensionNames' Maybe PhysicalDeviceFeatures
pEnabledFeatures'

instance es ~ '[] => Zero (DeviceCreateInfo es) where
  zero :: DeviceCreateInfo es
zero = Chain es
-> DeviceCreateFlags
-> Vector (SomeStruct DeviceQueueCreateInfo)
-> Vector ByteString
-> Vector ByteString
-> Maybe PhysicalDeviceFeatures
-> DeviceCreateInfo es
forall (es :: [*]).
Chain es
-> DeviceCreateFlags
-> Vector (SomeStruct DeviceQueueCreateInfo)
-> Vector ByteString
-> Vector ByteString
-> Maybe PhysicalDeviceFeatures
-> DeviceCreateInfo es
DeviceCreateInfo
           ()
           DeviceCreateFlags
forall a. Zero a => a
zero
           Vector (SomeStruct DeviceQueueCreateInfo)
forall a. Monoid a => a
mempty
           Vector ByteString
forall a. Monoid a => a
mempty
           Vector ByteString
forall a. Monoid a => a
mempty
           Maybe PhysicalDeviceFeatures
forall a. Maybe a
Nothing