{-# language CPP #-} -- No documentation found for Chapter "Promoted_From_VK_KHR_device_group" module Vulkan.Core11.Promoted_From_VK_KHR_device_group ( getDeviceGroupPeerMemoryFeatures , cmdSetDeviceMask , cmdDispatchBase , pattern PIPELINE_CREATE_DISPATCH_BASE , MemoryAllocateFlagsInfo(..) , DeviceGroupRenderPassBeginInfo(..) , DeviceGroupCommandBufferBeginInfo(..) , DeviceGroupSubmitInfo(..) , DeviceGroupBindSparseInfo(..) , StructureType(..) , PipelineCreateFlagBits(..) , PipelineCreateFlags , DependencyFlagBits(..) , DependencyFlags , PeerMemoryFeatureFlagBits(..) , PeerMemoryFeatureFlags , MemoryAllocateFlagBits(..) , MemoryAllocateFlags ) where import Vulkan.Internal.Utils (traceAroundEvent) import Control.Exception.Base (bracket) import Control.Monad (unless) import Control.Monad.IO.Class (liftIO) import Foreign.Marshal.Alloc (allocaBytes) import Foreign.Marshal.Alloc (callocBytes) import Foreign.Marshal.Alloc (free) import GHC.IO (throwIO) import GHC.Ptr (nullFunPtr) import Foreign.Ptr (nullPtr) import Foreign.Ptr (plusPtr) import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Cont (evalContT) import Data.Vector (generateM) import qualified Data.Vector (imapM_) import qualified Data.Vector (length) import Vulkan.CStruct (FromCStruct) import Vulkan.CStruct (FromCStruct(..)) import Vulkan.CStruct (ToCStruct) import Vulkan.CStruct (ToCStruct(..)) import Vulkan.Zero (Zero(..)) import Control.Monad.IO.Class (MonadIO) import Data.Typeable (Typeable) import Foreign.Storable (Storable) import Foreign.Storable (Storable(peek)) import Foreign.Storable (Storable(poke)) import qualified Foreign.Storable (Storable(..)) import GHC.Generics (Generic) import GHC.IO.Exception (IOErrorType(..)) import GHC.IO.Exception (IOException(..)) import Foreign.Ptr (FunPtr) import Foreign.Ptr (Ptr) import Data.Word (Word32) import Data.Kind (Type) import Control.Monad.Trans.Cont (ContT(..)) import Data.Vector (Vector) import Vulkan.CStruct.Utils (advancePtrBytes) import Vulkan.NamedType ((:::)) import Vulkan.Core10.Handles (CommandBuffer) import Vulkan.Core10.Handles (CommandBuffer(..)) import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer)) import Vulkan.Core10.Handles (CommandBuffer_T) import Vulkan.Core10.Handles (Device) import Vulkan.Core10.Handles (Device(..)) import Vulkan.Core10.Handles (Device(Device)) import Vulkan.Dynamic (DeviceCmds(pVkCmdDispatchBase)) import Vulkan.Dynamic (DeviceCmds(pVkCmdSetDeviceMask)) import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceGroupPeerMemoryFeatures)) import Vulkan.Core10.Handles (Device_T) import Vulkan.Core11.Enums.MemoryAllocateFlagBits (MemoryAllocateFlags) import Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits (PeerMemoryFeatureFlagBits(..)) import Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits (PeerMemoryFeatureFlags) import Vulkan.Core10.FundamentalTypes (Rect2D) import Vulkan.Core10.Enums.StructureType (StructureType) import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlags) import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlagBits(PIPELINE_CREATE_DISPATCH_BASE_BIT)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO)) import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlagBits(..)) import Vulkan.Core10.Enums.DependencyFlagBits (DependencyFlags) import Vulkan.Core11.Enums.MemoryAllocateFlagBits (MemoryAllocateFlagBits(..)) import Vulkan.Core11.Enums.MemoryAllocateFlagBits (MemoryAllocateFlags) import Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits (PeerMemoryFeatureFlagBits(..)) import Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits (PeerMemoryFeatureFlags) import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlagBits(..)) import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlags) import Vulkan.Core10.Enums.StructureType (StructureType(..)) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkGetDeviceGroupPeerMemoryFeatures :: FunPtr (Ptr Device_T -> Word32 -> Word32 -> Word32 -> Ptr PeerMemoryFeatureFlags -> IO ()) -> Ptr Device_T -> Word32 -> Word32 -> Word32 -> Ptr PeerMemoryFeatureFlags -> IO () -- | vkGetDeviceGroupPeerMemoryFeatures - Query supported peer memory -- features of a device -- -- == Valid Usage (Implicit) -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>, -- 'Vulkan.Core10.Handles.Device', -- 'Vulkan.Core11.Enums.PeerMemoryFeatureFlagBits.PeerMemoryFeatureFlags' getDeviceGroupPeerMemoryFeatures :: forall io . (MonadIO io) => -- | @device@ is the logical device that owns the memory. -- -- #VUID-vkGetDeviceGroupPeerMemoryFeatures-device-parameter# @device@ -- /must/ be a valid 'Vulkan.Core10.Handles.Device' handle Device -> -- | @heapIndex@ is the index of the memory heap from which the memory is -- allocated. -- -- #VUID-vkGetDeviceGroupPeerMemoryFeatures-heapIndex-00691# @heapIndex@ -- /must/ be less than @memoryHeapCount@ ("heapIndex" ::: Word32) -> -- | @localDeviceIndex@ is the device index of the physical device that -- performs the memory access. -- -- #VUID-vkGetDeviceGroupPeerMemoryFeatures-localDeviceIndex-00692# -- @localDeviceIndex@ /must/ be a valid device index -- -- #VUID-vkGetDeviceGroupPeerMemoryFeatures-localDeviceIndex-00694# -- @localDeviceIndex@ /must/ not equal @remoteDeviceIndex@ ("localDeviceIndex" ::: Word32) -> -- | @remoteDeviceIndex@ is the device index of the physical device that the -- memory is allocated for. -- -- #VUID-vkGetDeviceGroupPeerMemoryFeatures-remoteDeviceIndex-00693# -- @remoteDeviceIndex@ /must/ be a valid device index ("remoteDeviceIndex" ::: Word32) -> io (("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)) getDeviceGroupPeerMemoryFeatures :: forall (io :: * -> *). MonadIO io => Device -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> io ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) getDeviceGroupPeerMemoryFeatures Device device "heapIndex" ::: Word32 heapIndex "heapIndex" ::: Word32 localDeviceIndex "heapIndex" ::: Word32 remoteDeviceIndex = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c . forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do let vkGetDeviceGroupPeerMemoryFeaturesPtr :: FunPtr (Ptr Device_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)) -> IO ()) vkGetDeviceGroupPeerMemoryFeaturesPtr = DeviceCmds -> FunPtr (Ptr Device_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)) -> IO ()) pVkGetDeviceGroupPeerMemoryFeatures (case Device device of Device{DeviceCmds $sel:deviceCmds:Device :: Device -> DeviceCmds deviceCmds :: DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr Device_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)) -> IO ()) vkGetDeviceGroupPeerMemoryFeaturesPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkGetDeviceGroupPeerMemoryFeatures is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkGetDeviceGroupPeerMemoryFeatures' :: Ptr Device_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)) -> IO () vkGetDeviceGroupPeerMemoryFeatures' = FunPtr (Ptr Device_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)) -> IO ()) -> Ptr Device_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)) -> IO () mkVkGetDeviceGroupPeerMemoryFeatures FunPtr (Ptr Device_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)) -> IO ()) vkGetDeviceGroupPeerMemoryFeaturesPtr "pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) pPPeerMemoryFeatures <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c bracket (forall a. Int -> IO (Ptr a) callocBytes @PeerMemoryFeatureFlags Int 4) forall a. Ptr a -> IO () free forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. String -> IO a -> IO a traceAroundEvent String "vkGetDeviceGroupPeerMemoryFeatures" (Ptr Device_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags)) -> IO () vkGetDeviceGroupPeerMemoryFeatures' (Device -> Ptr Device_T deviceHandle (Device device)) ("heapIndex" ::: Word32 heapIndex) ("heapIndex" ::: Word32 localDeviceIndex) ("heapIndex" ::: Word32 remoteDeviceIndex) ("pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) pPPeerMemoryFeatures)) "peerMemoryFeatures" ::: PeerMemoryFeatureFlags pPeerMemoryFeatures <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> IO a peek @PeerMemoryFeatureFlags "pPeerMemoryFeatures" ::: Ptr ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags) pPPeerMemoryFeatures forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("peerMemoryFeatures" ::: PeerMemoryFeatureFlags pPeerMemoryFeatures) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdSetDeviceMask :: FunPtr (Ptr CommandBuffer_T -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> IO () -- | vkCmdSetDeviceMask - Modify device mask of a command buffer -- -- = Description -- -- @deviceMask@ is used to filter out subsequent commands from executing on -- all physical devices whose bit indices are not set in the mask, except -- commands beginning a render pass instance, commands transitioning to the -- next subpass in the render pass instance, and commands ending a render -- pass instance, which always execute on the set of physical devices whose -- bit indices are included in the @deviceMask@ member of the -- 'DeviceGroupRenderPassBeginInfo' structure passed to the command -- beginning the corresponding render pass instance. -- -- == Valid Usage -- -- - #VUID-vkCmdSetDeviceMask-deviceMask-00108# @deviceMask@ /must/ be a -- valid device mask value -- -- - #VUID-vkCmdSetDeviceMask-deviceMask-00109# @deviceMask@ /must/ not -- be zero -- -- - #VUID-vkCmdSetDeviceMask-deviceMask-00110# @deviceMask@ /must/ not -- include any set bits that were not in the -- 'DeviceGroupCommandBufferBeginInfo'::@deviceMask@ value when the -- command buffer began recording -- -- - #VUID-vkCmdSetDeviceMask-deviceMask-00111# If 'cmdSetDeviceMask' is -- called inside a render pass instance, @deviceMask@ /must/ not -- include any set bits that were not in the -- 'DeviceGroupRenderPassBeginInfo'::@deviceMask@ value when the render -- pass instance began recording -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdSetDeviceMask-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdSetDeviceMask-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdSetDeviceMask-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support graphics, compute, or transfer -- operations -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Both | Both | Graphics | State | -- | Secondary | | | Compute | | -- | | | | Transfer | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>, -- 'Vulkan.Core10.Handles.CommandBuffer' cmdSetDeviceMask :: forall io . (MonadIO io) => -- | @commandBuffer@ is command buffer whose current device mask is modified. CommandBuffer -> -- | @deviceMask@ is the new value of the current device mask. ("deviceMask" ::: Word32) -> io () cmdSetDeviceMask :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("heapIndex" ::: Word32) -> io () cmdSetDeviceMask CommandBuffer commandBuffer "heapIndex" ::: Word32 deviceMask = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdSetDeviceMaskPtr :: FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ()) vkCmdSetDeviceMaskPtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ()) pVkCmdSetDeviceMask (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds :: DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ()) vkCmdSetDeviceMaskPtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdSetDeviceMask is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdSetDeviceMask' :: Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO () vkCmdSetDeviceMask' = FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO () mkVkCmdSetDeviceMask FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO ()) vkCmdSetDeviceMaskPtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdSetDeviceMask" (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> IO () vkCmdSetDeviceMask' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("heapIndex" ::: Word32 deviceMask)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkCmdDispatchBase :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> Word32 -> IO () -- | vkCmdDispatchBase - Dispatch compute work items with non-zero base -- values for the workgroup IDs -- -- = Description -- -- When the command is executed, a global workgroup consisting of -- @groupCountX@ × @groupCountY@ × @groupCountZ@ local workgroups is -- assembled, with @WorkgroupId@ values ranging from [@baseGroup*@, -- @baseGroup*@ + @groupCount*@) in each component. -- 'Vulkan.Core10.CommandBufferBuilding.cmdDispatch' is equivalent to -- @vkCmdDispatchBase(0,0,0,groupCountX,groupCountY,groupCountZ)@. -- -- == Valid Usage -- -- - #VUID-vkCmdDispatchBase-magFilter-04553# If a -- 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or -- @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and -- @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is -- used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of -- this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' -- -- - #VUID-vkCmdDispatchBase-mipmapMode-04770# If a -- 'Vulkan.Core10.Handles.Sampler' created with @mipmapMode@ equal to -- 'Vulkan.Core10.Enums.SamplerMipmapMode.SAMPLER_MIPMAP_MODE_LINEAR' -- and @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' -- is used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of -- this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT' -- -- - #VUID-vkCmdDispatchBase-None-06479# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-depth-compare-operation depth comparison>, -- the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_SAMPLED_IMAGE_DEPTH_COMPARISON_BIT' -- -- - #VUID-vkCmdDispatchBase-None-02691# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed using atomic -- operations as a result of this command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT' -- -- - #VUID-vkCmdDispatchBase-None-07888# If a -- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_STORAGE_TEXEL_BUFFER' -- descriptor is accessed using atomic operations as a result of this -- command, then the storage texel buffer’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-buffer-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_TEXEL_BUFFER_ATOMIC_BIT' -- -- - #VUID-vkCmdDispatchBase-None-02692# If a -- 'Vulkan.Core10.Handles.ImageView' is sampled with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as a result of this -- command, then the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT' -- -- - #VUID-vkCmdDispatchBase-None-02693# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_filter_cubic VK_EXT_filter_cubic> -- extension is not enabled and any 'Vulkan.Core10.Handles.ImageView' -- is sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as a -- result of this command, it /must/ not have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' of -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY' -- -- - #VUID-vkCmdDispatchBase-filterCubic-02694# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as a result of this -- command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering, as specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - #VUID-vkCmdDispatchBase-filterCubicMinmax-02695# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' with a reduction mode -- of either -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN' -- or -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX' -- as a result of this command /must/ have a -- 'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that -- supports cubic filtering together with minmax filtering, as -- specified by -- 'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@ -- returned by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- -- - #VUID-vkCmdDispatchBase-cubicRangeClamp-09212# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-range-clamp cubicRangeClamp> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command -- -- [/must/ not have a 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'] -- @reductionMode@ equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- -- - #VUID-vkCmdDispatchBase-reductionMode-09213# Any -- 'Vulkan.Core10.Handles.ImageView' being sampled with a -- 'Vulkan.Core12.Promoted_From_VK_EXT_sampler_filter_minmax.SamplerReductionModeCreateInfo'::@reductionMode@ -- equal to -- 'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_WEIGHTED_AVERAGE_RANGECLAMP_QCOM' -- as a result of this command /must/ sample with -- 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' -- -- - #VUID-vkCmdDispatchBase-selectableCubicWeights-09214# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-filter-cubic-weight-selection selectableCubicWeights> -- feature is not enabled, then any 'Vulkan.Core10.Handles.ImageView' -- being sampled with 'Vulkan.Core10.Enums.Filter.FILTER_CUBIC_EXT' as -- a result of this command /must/ have -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.SamplerCubicWeightsCreateInfoQCOM'::@cubicWeights@ -- equal to -- 'Vulkan.Extensions.VK_QCOM_filter_cubic_weights.CUBIC_FILTER_WEIGHTS_CATMULL_ROM_QCOM' -- -- - #VUID-vkCmdDispatchBase-flags-02696# Any -- 'Vulkan.Core10.Handles.Image' created with a -- 'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV' -- sampled as a result of this command /must/ only be sampled using a -- 'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of -- 'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE' -- -- - #VUID-vkCmdDispatchBase-OpTypeImage-07027# For any -- 'Vulkan.Core10.Handles.ImageView' being written as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatchBase-OpTypeImage-07028# For any -- 'Vulkan.Core10.Handles.ImageView' being read as a storage image -- where the image format field of the @OpTypeImage@ is @Unknown@, the -- view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatchBase-OpTypeImage-07029# For any -- 'Vulkan.Core10.Handles.BufferView' being written as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@, the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_WRITE_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatchBase-OpTypeImage-07030# Any -- 'Vulkan.Core10.Handles.BufferView' being read as a storage texel -- buffer where the image format field of the @OpTypeImage@ is -- @Unknown@ then the view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkFormatProperties3 buffer features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_STORAGE_READ_WITHOUT_FORMAT_BIT' -- -- - #VUID-vkCmdDispatchBase-None-08600# For each set /n/ that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- a descriptor set /must/ have been bound to /n/ at the same pipeline -- bind point, with a 'Vulkan.Core10.Handles.PipelineLayout' that is -- compatible for set /n/, with the -- 'Vulkan.Core10.Handles.PipelineLayout' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' array that was used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDispatchBase-None-08601# For each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- a push constant value /must/ have been set for the same pipeline -- bind point, with a 'Vulkan.Core10.Handles.PipelineLayout' that is -- compatible for push constants, with the -- 'Vulkan.Core10.Handles.PipelineLayout' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDispatchBase-maintenance4-08602# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-maintenance4 maintenance4> -- feature is not enabled, then for each push constant that is -- statically used by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader>, -- a push constant value /must/ have been set for the same pipeline -- bind point, with a 'Vulkan.Core10.Handles.PipelineLayout' that is -- compatible for push constants, with the -- 'Vulkan.Core10.Handles.PipelineLayout' or -- 'Vulkan.Core10.Handles.DescriptorSetLayout' and -- 'Vulkan.Core10.PipelineLayout.PushConstantRange' arrays used to -- create the current 'Vulkan.Core10.Handles.Pipeline' or -- 'Vulkan.Extensions.Handles.ShaderEXT', as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???> -- -- - #VUID-vkCmdDispatchBase-None-08114# Descriptors in each bound -- descriptor set, specified via -- 'Vulkan.Core10.CommandBufferBuilding.cmdBindDescriptorSets', /must/ -- be valid if they are statically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command and the bound 'Vulkan.Core10.Handles.Pipeline' -- was not created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatchBase-None-08115# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via -- 'Vulkan.Core10.CommandBufferBuilding.cmdBindDescriptorSets', the -- bound 'Vulkan.Core10.Handles.Pipeline' /must/ have been created -- without -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatchBase-None-08116# Descriptors in bound descriptor -- buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- used by this command and the bound 'Vulkan.Core10.Handles.Pipeline' -- was created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatchBase-None-08604# Descriptors in bound descriptor -- buffers, specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- /must/ be valid if they are dynamically used by any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command -- -- - #VUID-vkCmdDispatchBase-None-08117# If the descriptors used by the -- 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point -- were specified via -- 'Vulkan.Extensions.VK_EXT_descriptor_buffer.cmdSetDescriptorBufferOffsetsEXT', -- the bound 'Vulkan.Core10.Handles.Pipeline' /must/ have been created -- with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT' -- -- - #VUID-vkCmdDispatchBase-None-08119# If a descriptor is dynamically -- used with a 'Vulkan.Core10.Handles.Pipeline' created with -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDispatchBase-None-08605# If a descriptor is dynamically -- used with a 'Vulkan.Extensions.Handles.ShaderEXT' created with a -- 'Vulkan.Core10.Handles.DescriptorSetLayout' that was created with -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_DESCRIPTOR_BUFFER_BIT_EXT', -- the descriptor memory /must/ be resident -- -- - #VUID-vkCmdDispatchBase-None-08606# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- feature is not enabled, a valid pipeline /must/ be bound to the -- pipeline bind point used by this command -- -- - #VUID-vkCmdDispatchBase-None-08607# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-shaderObject shaderObject> -- is enabled, either a valid pipeline /must/ be bound to the pipeline -- bind point used by this command, or a valid combination of valid and -- 'Vulkan.Core10.APIConstants.NULL_HANDLE' shader objects /must/ be -- bound to every supported shader stage corresponding to the pipeline -- bind point used by this command -- -- - #VUID-vkCmdDispatchBase-None-08608# If a pipeline is bound to the -- pipeline bind point used by this command, there /must/ not have been -- any calls to dynamic state setting commands for any state not -- specified as dynamic in the 'Vulkan.Core10.Handles.Pipeline' object -- bound to the pipeline bind point used by this command, since that -- pipeline was bound -- -- - #VUID-vkCmdDispatchBase-None-08609# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used to sample from any -- 'Vulkan.Core10.Handles.Image' with a -- 'Vulkan.Core10.Handles.ImageView' of the type -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY', -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or -- 'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in -- any shader stage -- -- - #VUID-vkCmdDispatchBase-None-08610# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions with -- @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage -- -- - #VUID-vkCmdDispatchBase-None-08611# If the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command or any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command accesses a -- 'Vulkan.Core10.Handles.Sampler' object that uses unnormalized -- coordinates, that sampler /must/ not be used with any of the SPIR-V -- @OpImageSample*@ or @OpImageSparseSample*@ instructions that -- includes a LOD bias or any offset values, in any shader stage -- -- - #VUID-vkCmdDispatchBase-uniformBuffers-06935# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a uniform buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @uniformBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDispatchBase-None-08612# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command accesses a uniform -- buffer, it /must/ not access values outside of the range of the -- buffer as specified in the descriptor set bound to the same pipeline -- bind point -- -- - #VUID-vkCmdDispatchBase-storageBuffers-06936# If any stage of the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command accesses a storage buffer, and that stage -- was created without enabling either -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_EXT' -- or -- 'Vulkan.Extensions.VK_EXT_pipeline_robustness.PIPELINE_ROBUSTNESS_BUFFER_BEHAVIOR_ROBUST_BUFFER_ACCESS_2_EXT' -- for @storageBuffers@, and the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, that stage /must/ not access values outside -- of the range of the buffer as specified in the descriptor set bound -- to the same pipeline bind point -- -- - #VUID-vkCmdDispatchBase-None-08613# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robustBufferAccess> -- feature is not enabled, and any -- 'Vulkan.Extensions.Handles.ShaderEXT' bound to a stage corresponding -- to the pipeline bind point used by this command accesses a storage -- buffer, it /must/ not access values outside of the range of the -- buffer as specified in the descriptor set bound to the same pipeline -- bind point -- -- - #VUID-vkCmdDispatchBase-commandBuffer-02707# If @commandBuffer@ is -- an unprotected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, any resource accessed by -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding bound shaders> -- /must/ not be a protected resource -- -- - #VUID-vkCmdDispatchBase-None-06550# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ only be used with @OpImageSample*@ or -- @OpImageSparseSample*@ instructions -- -- - #VUID-vkCmdDispatchBase-ConstOffset-06551# If -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-binding a bound shader> -- accesses a 'Vulkan.Core10.Handles.Sampler' or -- 'Vulkan.Core10.Handles.ImageView' object that enables -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#samplers-YCbCr-conversion sampler Y′CBCR conversion>, -- that object /must/ not use the @ConstOffset@ and @Offset@ operands -- -- - #VUID-vkCmdDispatchBase-viewType-07752# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the image view’s @viewType@ /must/ match the @Dim@ -- operand of the @OpTypeImage@ as described in -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-operation-validation ???> -- -- - #VUID-vkCmdDispatchBase-format-07753# If a -- 'Vulkan.Core10.Handles.ImageView' is accessed as a result of this -- command, then the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#formats-numericformat numeric type> -- of the image view’s @format@ and the @Sampled@ @Type@ operand of the -- @OpTypeImage@ /must/ match -- -- - #VUID-vkCmdDispatchBase-OpImageWrite-08795# If a -- 'Vulkan.Core10.Handles.ImageView' created with a format other than -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have at least as many -- components as the image view’s format -- -- - #VUID-vkCmdDispatchBase-OpImageWrite-08796# If a -- 'Vulkan.Core10.Handles.ImageView' created with the format -- 'Vulkan.Core10.Enums.Format.FORMAT_A8_UNORM_KHR' is accessed using -- @OpImageWrite@ as a result of this command, then the @Type@ of the -- @Texel@ operand of that instruction /must/ have four components -- -- - #VUID-vkCmdDispatchBase-OpImageWrite-04469# If a -- 'Vulkan.Core10.Handles.BufferView' is accessed using @OpImageWrite@ -- as a result of this command, then the @Type@ of the @Texel@ operand -- of that instruction /must/ have at least as many components as the -- buffer view’s format -- -- - #VUID-vkCmdDispatchBase-SampledType-04470# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDispatchBase-SampledType-04471# If a -- 'Vulkan.Core10.Handles.ImageView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32 -- -- - #VUID-vkCmdDispatchBase-SampledType-04472# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a 64-bit component -- width is accessed as a result of this command, the @SampledType@ of -- the @OpTypeImage@ operand of that instruction /must/ have a @Width@ -- of 64 -- -- - #VUID-vkCmdDispatchBase-SampledType-04473# If a -- 'Vulkan.Core10.Handles.BufferView' with a -- 'Vulkan.Core10.Enums.Format.Format' that has a component width less -- than 64-bit is accessed as a result of this command, the -- @SampledType@ of the @OpTypeImage@ operand of that instruction -- /must/ have a @Width@ of 32 -- -- - #VUID-vkCmdDispatchBase-sparseImageInt64Atomics-04474# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Image' objects -- created with the -- 'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command -- -- - #VUID-vkCmdDispatchBase-sparseImageInt64Atomics-04475# If the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics> -- feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects -- created with the -- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT' -- flag /must/ not be accessed by atomic instructions through an -- @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this -- command -- -- - #VUID-vkCmdDispatchBase-OpImageWeightedSampleQCOM-06971# If -- @OpImageWeightedSampleQCOM@ is used to sample a -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_SAMPLED_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDispatchBase-OpImageWeightedSampleQCOM-06972# If -- @OpImageWeightedSampleQCOM@ uses a 'Vulkan.Core10.Handles.ImageView' -- as a sample weight image as a result of this command, then the image -- view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_WEIGHT_IMAGE_BIT_QCOM' -- -- - #VUID-vkCmdDispatchBase-OpImageBoxFilterQCOM-06973# If -- @OpImageBoxFilterQCOM@ is used to sample a -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BOX_FILTER_SAMPLED_BIT_QCOM' -- -- - #VUID-vkCmdDispatchBase-OpImageBlockMatchSSDQCOM-06974# If -- @OpImageBlockMatchSSDQCOM@ is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchBase-OpImageBlockMatchSADQCOM-06975# If -- @OpImageBlockMatchSADQCOM@ is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchBase-OpImageBlockMatchSADQCOM-06976# If -- @OpImageBlockMatchSADQCOM@ or OpImageBlockMatchSSDQCOM is used to -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDispatchBase-OpImageWeightedSampleQCOM-06977# If -- @OpImageWeightedSampleQCOM@, @OpImageBoxFilterQCOM@, -- @OpImageBlockMatchWindowSSDQCOM@, @OpImageBlockMatchWindowSADQCOM@, -- @OpImageBlockMatchGatherSSDQCOM@, @OpImageBlockMatchGatherSADQCOM@, -- @OpImageBlockMatchSSDQCOM@, or @OpImageBlockMatchSADQCOM@ uses a -- 'Vulkan.Core10.Handles.Sampler' as a result of this command, then -- the sampler /must/ have been created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchBase-OpImageWeightedSampleQCOM-06978# If any -- command other than @OpImageWeightedSampleQCOM@, -- @OpImageBoxFilterQCOM@, @OpImageBlockMatchWindowSSDQCOM@, -- @OpImageBlockMatchWindowSADQCOM@, @OpImageBlockMatchGatherSSDQCOM@, -- @OpImageBlockMatchGatherSADQCOM@, @OpImageBlockMatchSSDQCOM@, or -- @OpImageBlockMatchSADQCOM@ uses a 'Vulkan.Core10.Handles.Sampler' as -- a result of this command, then the sampler /must/ not have been -- created with -- 'Vulkan.Core10.Enums.SamplerCreateFlagBits.SAMPLER_CREATE_IMAGE_PROCESSING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchBase-OpImageBlockMatchWindow-09215# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features> -- /must/ contain -- 'Vulkan.Core13.Enums.FormatFeatureFlags2.FORMAT_FEATURE_2_BLOCK_MATCHING_BIT_QCOM' -- -- - #VUID-vkCmdDispatchBase-OpImageBlockMatchWindow-09216# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- instruction is used to read from an -- 'Vulkan.Core10.Handles.ImageView' as a result of this command, then -- the image view’s format /must/ be a single-component format. -- -- - #VUID-vkCmdDispatchBase-OpImageBlockMatchWindow-09217# If a -- @OpImageBlockMatchWindow*QCOM@ or @OpImageBlockMatchGather*QCOM@ -- read from a reference image as result of this command, then the -- specified reference coordinates /must/ not fail -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#textures-integer-coordinate-validation integer texel coordinate validation> -- -- - #VUID-vkCmdDispatchBase-None-07288# Any shader invocation executed -- by this command /must/ -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-termination terminate> -- -- - #VUID-vkCmdDispatchBase-commandBuffer-02712# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, any resource written to by the -- 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind -- point used by this command /must/ not be an unprotected resource -- -- - #VUID-vkCmdDispatchBase-commandBuffer-02713# If @commandBuffer@ is a -- protected command buffer and -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-protectedNoFault protectedNoFault> -- is not supported, pipeline stages other than the framebuffer-space -- and compute stages in the 'Vulkan.Core10.Handles.Pipeline' object -- bound to the pipeline bind point used by this command /must/ not -- write to any resource -- -- - #VUID-vkCmdDispatchBase-commandBuffer-04617# If any of the shader -- stages of the 'Vulkan.Core10.Handles.Pipeline' bound to the pipeline -- bind point used by this command uses the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#spirvenv-capabilities-table-RayQueryKHR RayQueryKHR> -- capability, then @commandBuffer@ /must/ not be a protected command -- buffer -- -- - #VUID-vkCmdDispatchBase-baseGroupX-00421# @baseGroupX@ /must/ be -- less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0] -- -- - #VUID-vkCmdDispatchBase-baseGroupX-00422# @baseGroupY@ /must/ be -- less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1] -- -- - #VUID-vkCmdDispatchBase-baseGroupZ-00423# @baseGroupZ@ /must/ be -- less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2] -- -- - #VUID-vkCmdDispatchBase-groupCountX-00424# @groupCountX@ /must/ be -- less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0] -- minus @baseGroupX@ -- -- - #VUID-vkCmdDispatchBase-groupCountY-00425# @groupCountY@ /must/ be -- less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1] -- minus @baseGroupY@ -- -- - #VUID-vkCmdDispatchBase-groupCountZ-00426# @groupCountZ@ /must/ be -- less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2] -- minus @baseGroupZ@ -- -- - #VUID-vkCmdDispatchBase-baseGroupX-00427# If any of @baseGroupX@, -- @baseGroupY@, or @baseGroupZ@ are not zero, then the bound compute -- pipeline /must/ have been created with the -- 'PIPELINE_CREATE_DISPATCH_BASE' flag -- -- == Valid Usage (Implicit) -- -- - #VUID-vkCmdDispatchBase-commandBuffer-parameter# @commandBuffer@ -- /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle -- -- - #VUID-vkCmdDispatchBase-commandBuffer-recording# @commandBuffer@ -- /must/ be in the -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state> -- -- - #VUID-vkCmdDispatchBase-commandBuffer-cmdpool# The -- 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was -- allocated from /must/ support compute operations -- -- - #VUID-vkCmdDispatchBase-renderpass# This command /must/ only be -- called outside of a render pass instance -- -- - #VUID-vkCmdDispatchBase-videocoding# This command /must/ only be -- called outside of a video coding scope -- -- == Host Synchronization -- -- - Host access to @commandBuffer@ /must/ be externally synchronized -- -- - Host access to the 'Vulkan.Core10.Handles.CommandPool' that -- @commandBuffer@ was allocated from /must/ be externally synchronized -- -- == Command Properties -- -- \' -- -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> | -- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+ -- | Primary | Outside | Outside | Compute | Action | -- | Secondary | | | | | -- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+ -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>, -- 'Vulkan.Core10.Handles.CommandBuffer' cmdDispatchBase :: forall io . (MonadIO io) => -- | @commandBuffer@ is the command buffer into which the command will be -- recorded. CommandBuffer -> -- | @baseGroupX@ is the start value for the X component of @WorkgroupId@. ("baseGroupX" ::: Word32) -> -- | @baseGroupY@ is the start value for the Y component of @WorkgroupId@. ("baseGroupY" ::: Word32) -> -- | @baseGroupZ@ is the start value for the Z component of @WorkgroupId@. ("baseGroupZ" ::: Word32) -> -- | @groupCountX@ is the number of local workgroups to dispatch in the X -- dimension. ("groupCountX" ::: Word32) -> -- | @groupCountY@ is the number of local workgroups to dispatch in the Y -- dimension. ("groupCountY" ::: Word32) -> -- | @groupCountZ@ is the number of local workgroups to dispatch in the Z -- dimension. ("groupCountZ" ::: Word32) -> io () cmdDispatchBase :: forall (io :: * -> *). MonadIO io => CommandBuffer -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> io () cmdDispatchBase CommandBuffer commandBuffer "heapIndex" ::: Word32 baseGroupX "heapIndex" ::: Word32 baseGroupY "heapIndex" ::: Word32 baseGroupZ "heapIndex" ::: Word32 groupCountX "heapIndex" ::: Word32 groupCountY "heapIndex" ::: Word32 groupCountZ = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkCmdDispatchBasePtr :: FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()) vkCmdDispatchBasePtr = DeviceCmds -> FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()) pVkCmdDispatchBase (case CommandBuffer commandBuffer of CommandBuffer{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()) vkCmdDispatchBasePtr forall a. Eq a => a -> a -> Bool /= forall a. FunPtr a nullFunPtr) forall a b. (a -> b) -> a -> b $ forall e a. Exception e => e -> IO a throwIO forall a b. (a -> b) -> a -> b $ Maybe Handle -> IOErrorType -> String -> String -> Maybe CInt -> Maybe String -> IOException IOError forall a. Maybe a Nothing IOErrorType InvalidArgument String "" String "The function pointer for vkCmdDispatchBase is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkCmdDispatchBase' :: Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO () vkCmdDispatchBase' = FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()) -> Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO () mkVkCmdDispatchBase FunPtr (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO ()) vkCmdDispatchBasePtr forall a. String -> IO a -> IO a traceAroundEvent String "vkCmdDispatchBase" (Ptr CommandBuffer_T -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> IO () vkCmdDispatchBase' (CommandBuffer -> Ptr CommandBuffer_T commandBufferHandle (CommandBuffer commandBuffer)) ("heapIndex" ::: Word32 baseGroupX) ("heapIndex" ::: Word32 baseGroupY) ("heapIndex" ::: Word32 baseGroupZ) ("heapIndex" ::: Word32 groupCountX) ("heapIndex" ::: Word32 groupCountY) ("heapIndex" ::: Word32 groupCountZ)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ () -- No documentation found for TopLevel "VK_PIPELINE_CREATE_DISPATCH_BASE" pattern $bPIPELINE_CREATE_DISPATCH_BASE :: PipelineCreateFlagBits $mPIPELINE_CREATE_DISPATCH_BASE :: forall {r}. PipelineCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r PIPELINE_CREATE_DISPATCH_BASE = PIPELINE_CREATE_DISPATCH_BASE_BIT -- | VkMemoryAllocateFlagsInfo - Structure controlling how many instances of -- memory will be allocated -- -- = Description -- -- If -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_MASK_BIT' -- is not set, the number of instances allocated depends on whether -- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_MULTI_INSTANCE_BIT' -- is set in the memory heap. If -- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_MULTI_INSTANCE_BIT' -- is set, then memory is allocated for every physical device in the -- logical device (as if @deviceMask@ has bits set for all device indices). -- If -- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_MULTI_INSTANCE_BIT' -- is not set, then a single instance of memory is allocated (as if -- @deviceMask@ is set to one). -- -- On some implementations, allocations from a multi-instance heap /may/ -- consume memory on all physical devices even if the @deviceMask@ excludes -- some devices. If -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group_creation.PhysicalDeviceGroupProperties'::@subsetAllocation@ -- is 'Vulkan.Core10.FundamentalTypes.TRUE', then memory is only consumed -- for the devices in the device mask. -- -- Note -- -- In practice, most allocations on a multi-instance heap will be allocated -- across all physical devices. Unicast allocation support is an optional -- optimization for a minority of allocations. -- -- == Valid Usage -- -- - #VUID-VkMemoryAllocateFlagsInfo-deviceMask-00675# If -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_MASK_BIT' -- is set, @deviceMask@ /must/ be a valid device mask -- -- - #VUID-VkMemoryAllocateFlagsInfo-deviceMask-00676# If -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_MASK_BIT' -- is set, @deviceMask@ /must/ not be zero -- -- == Valid Usage (Implicit) -- -- - #VUID-VkMemoryAllocateFlagsInfo-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO' -- -- - #VUID-VkMemoryAllocateFlagsInfo-flags-parameter# @flags@ /must/ be a -- valid combination of -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MemoryAllocateFlagBits' -- values -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>, -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MemoryAllocateFlags', -- 'Vulkan.Core10.Enums.StructureType.StructureType' data MemoryAllocateFlagsInfo = MemoryAllocateFlagsInfo { -- | @flags@ is a bitmask of -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MemoryAllocateFlagBits' -- controlling the allocation. MemoryAllocateFlagsInfo -> MemoryAllocateFlags flags :: MemoryAllocateFlags , -- | @deviceMask@ is a mask of physical devices in the logical device, -- indicating that memory /must/ be allocated on each device in the mask, -- if -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_MASK_BIT' -- is set in @flags@. MemoryAllocateFlagsInfo -> "heapIndex" ::: Word32 deviceMask :: Word32 } deriving (Typeable, MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool $c/= :: MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool == :: MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool $c== :: MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (MemoryAllocateFlagsInfo) #endif deriving instance Show MemoryAllocateFlagsInfo instance ToCStruct MemoryAllocateFlagsInfo where withCStruct :: forall b. MemoryAllocateFlagsInfo -> (Ptr MemoryAllocateFlagsInfo -> IO b) -> IO b withCStruct MemoryAllocateFlagsInfo x Ptr MemoryAllocateFlagsInfo -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 24 forall a b. (a -> b) -> a -> b $ \Ptr MemoryAllocateFlagsInfo p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr MemoryAllocateFlagsInfo p MemoryAllocateFlagsInfo x (Ptr MemoryAllocateFlagsInfo -> IO b f Ptr MemoryAllocateFlagsInfo p) pokeCStruct :: forall b. Ptr MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> IO b -> IO b pokeCStruct Ptr MemoryAllocateFlagsInfo p MemoryAllocateFlagsInfo{"heapIndex" ::: Word32 MemoryAllocateFlags deviceMask :: "heapIndex" ::: Word32 flags :: MemoryAllocateFlags $sel:deviceMask:MemoryAllocateFlagsInfo :: MemoryAllocateFlagsInfo -> "heapIndex" ::: Word32 $sel:flags:MemoryAllocateFlagsInfo :: MemoryAllocateFlagsInfo -> MemoryAllocateFlags ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr MemoryAllocateFlagsInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr MemoryAllocateFlagsInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr MemoryAllocateFlagsInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr MemoryAllocateFlags)) (MemoryAllocateFlags flags) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr MemoryAllocateFlagsInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) ("heapIndex" ::: Word32 deviceMask) IO b f cStructSize :: Int cStructSize = Int 24 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr MemoryAllocateFlagsInfo -> IO b -> IO b pokeZeroCStruct Ptr MemoryAllocateFlagsInfo p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr MemoryAllocateFlagsInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_MEMORY_ALLOCATE_FLAGS_INFO) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr MemoryAllocateFlagsInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr MemoryAllocateFlagsInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct MemoryAllocateFlagsInfo where peekCStruct :: Ptr MemoryAllocateFlagsInfo -> IO MemoryAllocateFlagsInfo peekCStruct Ptr MemoryAllocateFlagsInfo p = do MemoryAllocateFlags flags <- forall a. Storable a => Ptr a -> IO a peek @MemoryAllocateFlags ((Ptr MemoryAllocateFlagsInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr MemoryAllocateFlags)) "heapIndex" ::: Word32 deviceMask <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr MemoryAllocateFlagsInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ MemoryAllocateFlags -> ("heapIndex" ::: Word32) -> MemoryAllocateFlagsInfo MemoryAllocateFlagsInfo MemoryAllocateFlags flags "heapIndex" ::: Word32 deviceMask instance Storable MemoryAllocateFlagsInfo where sizeOf :: MemoryAllocateFlagsInfo -> Int sizeOf ~MemoryAllocateFlagsInfo _ = Int 24 alignment :: MemoryAllocateFlagsInfo -> Int alignment ~MemoryAllocateFlagsInfo _ = Int 8 peek :: Ptr MemoryAllocateFlagsInfo -> IO MemoryAllocateFlagsInfo peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr MemoryAllocateFlagsInfo -> MemoryAllocateFlagsInfo -> IO () poke Ptr MemoryAllocateFlagsInfo ptr MemoryAllocateFlagsInfo poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr MemoryAllocateFlagsInfo ptr MemoryAllocateFlagsInfo poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero MemoryAllocateFlagsInfo where zero :: MemoryAllocateFlagsInfo zero = MemoryAllocateFlags -> ("heapIndex" ::: Word32) -> MemoryAllocateFlagsInfo MemoryAllocateFlagsInfo forall a. Zero a => a zero forall a. Zero a => a zero -- | VkDeviceGroupRenderPassBeginInfo - Set the initial device mask and -- render areas for a render pass instance -- -- = Description -- -- The @deviceMask@ serves several purposes. It is an upper bound on the -- set of physical devices that /can/ be used during the render pass -- instance, and the initial device mask when the render pass instance -- begins. In addition, commands transitioning to the next subpass in a -- render pass instance and commands ending the render pass instance, and, -- accordingly render pass -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-load-operations load>, -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-store-operations store>, -- and -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#renderpass-resolve-operations multisample resolve> -- operations and subpass dependencies corresponding to the render pass -- instance, are executed on the physical devices included in the device -- mask provided here. -- -- If @deviceRenderAreaCount@ is not zero, then the elements of -- @pDeviceRenderAreas@ override the value of -- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo'::@renderArea@, -- and provide a render area specific to each physical device. These render -- areas serve the same purpose as -- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo'::@renderArea@, -- including controlling the region of attachments that are cleared by -- 'Vulkan.Core10.Enums.AttachmentLoadOp.ATTACHMENT_LOAD_OP_CLEAR' and that -- are resolved into resolve attachments. -- -- If this structure is not present, the render pass instance’s device mask -- is the value of 'DeviceGroupCommandBufferBeginInfo'::@deviceMask@. If -- this structure is not present or if @deviceRenderAreaCount@ is zero, -- 'Vulkan.Core10.CommandBufferBuilding.RenderPassBeginInfo'::@renderArea@ -- is used for all physical devices. -- -- == Valid Usage -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-deviceMask-00905# -- @deviceMask@ /must/ be a valid device mask value -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-deviceMask-00906# -- @deviceMask@ /must/ not be zero -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-deviceMask-00907# -- @deviceMask@ /must/ be a subset of the command buffer’s initial -- device mask -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-deviceRenderAreaCount-00908# -- @deviceRenderAreaCount@ /must/ either be zero or equal to the number -- of physical devices in the logical device -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-offset-06166# The @offset.x@ -- member of any element of @pDeviceRenderAreas@ /must/ be greater than -- or equal to 0 -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-offset-06167# The @offset.y@ -- member of any element of @pDeviceRenderAreas@ /must/ be greater than -- or equal to 0 -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-offset-06168# The sum of the -- @offset.x@ and @extent.width@ members of any element of -- @pDeviceRenderAreas@ /must/ be less than or equal to -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-maxFramebufferWidth maxFramebufferWidth> -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-offset-06169# The sum of the -- @offset.y@ and @extent.height@ members of any element of -- @pDeviceRenderAreas@ /must/ be less than or equal to -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-maxFramebufferHeight maxFramebufferHeight> -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-extent-08998# The -- @extent.width@ member of any element of @pDeviceRenderAreas@ /must/ -- be greater than 0 -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-extent-08999# The -- @extent.height@ member of any element of @pDeviceRenderAreas@ /must/ -- be greater than 0 -- -- == Valid Usage (Implicit) -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-sType-sType# @sType@ /must/ -- be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO' -- -- - #VUID-VkDeviceGroupRenderPassBeginInfo-pDeviceRenderAreas-parameter# -- If @deviceRenderAreaCount@ is not @0@, @pDeviceRenderAreas@ /must/ -- be a valid pointer to an array of @deviceRenderAreaCount@ -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>, -- 'Vulkan.Core10.FundamentalTypes.Rect2D', -- 'Vulkan.Core10.Enums.StructureType.StructureType' data DeviceGroupRenderPassBeginInfo = DeviceGroupRenderPassBeginInfo { -- | @deviceMask@ is the device mask for the render pass instance. DeviceGroupRenderPassBeginInfo -> "heapIndex" ::: Word32 deviceMask :: Word32 , -- | @pDeviceRenderAreas@ is a pointer to an array of -- 'Vulkan.Core10.FundamentalTypes.Rect2D' structures defining the render -- area for each physical device. DeviceGroupRenderPassBeginInfo -> Vector Rect2D deviceRenderAreas :: Vector Rect2D } deriving (Typeable) #if defined(GENERIC_INSTANCES) deriving instance Generic (DeviceGroupRenderPassBeginInfo) #endif deriving instance Show DeviceGroupRenderPassBeginInfo instance ToCStruct DeviceGroupRenderPassBeginInfo where withCStruct :: forall b. DeviceGroupRenderPassBeginInfo -> (Ptr DeviceGroupRenderPassBeginInfo -> IO b) -> IO b withCStruct DeviceGroupRenderPassBeginInfo x Ptr DeviceGroupRenderPassBeginInfo -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 32 forall a b. (a -> b) -> a -> b $ \Ptr DeviceGroupRenderPassBeginInfo p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr DeviceGroupRenderPassBeginInfo p DeviceGroupRenderPassBeginInfo x (Ptr DeviceGroupRenderPassBeginInfo -> IO b f Ptr DeviceGroupRenderPassBeginInfo p) pokeCStruct :: forall b. Ptr DeviceGroupRenderPassBeginInfo -> DeviceGroupRenderPassBeginInfo -> IO b -> IO b pokeCStruct Ptr DeviceGroupRenderPassBeginInfo p DeviceGroupRenderPassBeginInfo{"heapIndex" ::: Word32 Vector Rect2D deviceRenderAreas :: Vector Rect2D deviceMask :: "heapIndex" ::: Word32 $sel:deviceRenderAreas:DeviceGroupRenderPassBeginInfo :: DeviceGroupRenderPassBeginInfo -> Vector Rect2D $sel:deviceMask:DeviceGroupRenderPassBeginInfo :: DeviceGroupRenderPassBeginInfo -> "heapIndex" ::: Word32 ..} IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) ("heapIndex" ::: Word32 deviceMask) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector Rect2D deviceRenderAreas)) :: Word32)) Ptr Rect2D pPDeviceRenderAreas' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Rect2D ((forall a. Vector a -> Int Data.Vector.length (Vector Rect2D deviceRenderAreas)) forall a. Num a => a -> a -> a * Int 16) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i Rect2D e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr Rect2D pPDeviceRenderAreas' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 16 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Rect2D) (Rect2D e)) (Vector Rect2D deviceRenderAreas) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr (Ptr Rect2D))) (Ptr Rect2D pPDeviceRenderAreas') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f cStructSize :: Int cStructSize = Int 32 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr DeviceGroupRenderPassBeginInfo -> IO b -> IO b pokeZeroCStruct Ptr DeviceGroupRenderPassBeginInfo p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_DEVICE_GROUP_RENDER_PASS_BEGIN_INFO) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct DeviceGroupRenderPassBeginInfo where peekCStruct :: Ptr DeviceGroupRenderPassBeginInfo -> IO DeviceGroupRenderPassBeginInfo peekCStruct Ptr DeviceGroupRenderPassBeginInfo p = do "heapIndex" ::: Word32 deviceMask <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) "heapIndex" ::: Word32 deviceRenderAreaCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) Ptr Rect2D pDeviceRenderAreas <- forall a. Storable a => Ptr a -> IO a peek @(Ptr Rect2D) ((Ptr DeviceGroupRenderPassBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr (Ptr Rect2D))) Vector Rect2D pDeviceRenderAreas' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral "heapIndex" ::: Word32 deviceRenderAreaCount) (\Int i -> forall a. FromCStruct a => Ptr a -> IO a peekCStruct @Rect2D ((Ptr Rect2D pDeviceRenderAreas forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 16 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Rect2D))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("heapIndex" ::: Word32) -> Vector Rect2D -> DeviceGroupRenderPassBeginInfo DeviceGroupRenderPassBeginInfo "heapIndex" ::: Word32 deviceMask Vector Rect2D pDeviceRenderAreas' instance Zero DeviceGroupRenderPassBeginInfo where zero :: DeviceGroupRenderPassBeginInfo zero = ("heapIndex" ::: Word32) -> Vector Rect2D -> DeviceGroupRenderPassBeginInfo DeviceGroupRenderPassBeginInfo forall a. Zero a => a zero forall a. Monoid a => a mempty -- | VkDeviceGroupCommandBufferBeginInfo - Set the initial device mask for a -- command buffer -- -- = Description -- -- The initial device mask also acts as an upper bound on the set of -- devices that /can/ ever be in the device mask in the command buffer. -- -- If this structure is not present, the initial value of a command -- buffer’s device mask is set to include all physical devices in the -- logical device when the command buffer begins recording. -- -- == Valid Usage (Implicit) -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>, -- 'Vulkan.Core10.Enums.StructureType.StructureType' data DeviceGroupCommandBufferBeginInfo = DeviceGroupCommandBufferBeginInfo { -- | @deviceMask@ is the initial value of the command buffer’s device mask. -- -- #VUID-VkDeviceGroupCommandBufferBeginInfo-deviceMask-00106# @deviceMask@ -- /must/ be a valid device mask value -- -- #VUID-VkDeviceGroupCommandBufferBeginInfo-deviceMask-00107# @deviceMask@ -- /must/ not be zero DeviceGroupCommandBufferBeginInfo -> "heapIndex" ::: Word32 deviceMask :: Word32 } deriving (Typeable, DeviceGroupCommandBufferBeginInfo -> DeviceGroupCommandBufferBeginInfo -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: DeviceGroupCommandBufferBeginInfo -> DeviceGroupCommandBufferBeginInfo -> Bool $c/= :: DeviceGroupCommandBufferBeginInfo -> DeviceGroupCommandBufferBeginInfo -> Bool == :: DeviceGroupCommandBufferBeginInfo -> DeviceGroupCommandBufferBeginInfo -> Bool $c== :: DeviceGroupCommandBufferBeginInfo -> DeviceGroupCommandBufferBeginInfo -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (DeviceGroupCommandBufferBeginInfo) #endif deriving instance Show DeviceGroupCommandBufferBeginInfo instance ToCStruct DeviceGroupCommandBufferBeginInfo where withCStruct :: forall b. DeviceGroupCommandBufferBeginInfo -> (Ptr DeviceGroupCommandBufferBeginInfo -> IO b) -> IO b withCStruct DeviceGroupCommandBufferBeginInfo x Ptr DeviceGroupCommandBufferBeginInfo -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 24 forall a b. (a -> b) -> a -> b $ \Ptr DeviceGroupCommandBufferBeginInfo p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr DeviceGroupCommandBufferBeginInfo p DeviceGroupCommandBufferBeginInfo x (Ptr DeviceGroupCommandBufferBeginInfo -> IO b f Ptr DeviceGroupCommandBufferBeginInfo p) pokeCStruct :: forall b. Ptr DeviceGroupCommandBufferBeginInfo -> DeviceGroupCommandBufferBeginInfo -> IO b -> IO b pokeCStruct Ptr DeviceGroupCommandBufferBeginInfo p DeviceGroupCommandBufferBeginInfo{"heapIndex" ::: Word32 deviceMask :: "heapIndex" ::: Word32 $sel:deviceMask:DeviceGroupCommandBufferBeginInfo :: DeviceGroupCommandBufferBeginInfo -> "heapIndex" ::: Word32 ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupCommandBufferBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupCommandBufferBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupCommandBufferBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) ("heapIndex" ::: Word32 deviceMask) IO b f cStructSize :: Int cStructSize = Int 24 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr DeviceGroupCommandBufferBeginInfo -> IO b -> IO b pokeZeroCStruct Ptr DeviceGroupCommandBufferBeginInfo p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupCommandBufferBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_DEVICE_GROUP_COMMAND_BUFFER_BEGIN_INFO) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupCommandBufferBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupCommandBufferBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct DeviceGroupCommandBufferBeginInfo where peekCStruct :: Ptr DeviceGroupCommandBufferBeginInfo -> IO DeviceGroupCommandBufferBeginInfo peekCStruct Ptr DeviceGroupCommandBufferBeginInfo p = do "heapIndex" ::: Word32 deviceMask <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr DeviceGroupCommandBufferBeginInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("heapIndex" ::: Word32) -> DeviceGroupCommandBufferBeginInfo DeviceGroupCommandBufferBeginInfo "heapIndex" ::: Word32 deviceMask instance Storable DeviceGroupCommandBufferBeginInfo where sizeOf :: DeviceGroupCommandBufferBeginInfo -> Int sizeOf ~DeviceGroupCommandBufferBeginInfo _ = Int 24 alignment :: DeviceGroupCommandBufferBeginInfo -> Int alignment ~DeviceGroupCommandBufferBeginInfo _ = Int 8 peek :: Ptr DeviceGroupCommandBufferBeginInfo -> IO DeviceGroupCommandBufferBeginInfo peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr DeviceGroupCommandBufferBeginInfo -> DeviceGroupCommandBufferBeginInfo -> IO () poke Ptr DeviceGroupCommandBufferBeginInfo ptr DeviceGroupCommandBufferBeginInfo poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr DeviceGroupCommandBufferBeginInfo ptr DeviceGroupCommandBufferBeginInfo poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero DeviceGroupCommandBufferBeginInfo where zero :: DeviceGroupCommandBufferBeginInfo zero = ("heapIndex" ::: Word32) -> DeviceGroupCommandBufferBeginInfo DeviceGroupCommandBufferBeginInfo forall a. Zero a => a zero -- | VkDeviceGroupSubmitInfo - Structure indicating which physical devices -- execute semaphore operations and command buffers -- -- = Description -- -- If this structure is not present, semaphore operations and command -- buffers execute on device index zero. -- -- == Valid Usage -- -- - #VUID-VkDeviceGroupSubmitInfo-waitSemaphoreCount-00082# -- @waitSemaphoreCount@ /must/ equal -- 'Vulkan.Core10.Queue.SubmitInfo'::@waitSemaphoreCount@ -- -- - #VUID-VkDeviceGroupSubmitInfo-commandBufferCount-00083# -- @commandBufferCount@ /must/ equal -- 'Vulkan.Core10.Queue.SubmitInfo'::@commandBufferCount@ -- -- - #VUID-VkDeviceGroupSubmitInfo-signalSemaphoreCount-00084# -- @signalSemaphoreCount@ /must/ equal -- 'Vulkan.Core10.Queue.SubmitInfo'::@signalSemaphoreCount@ -- -- - #VUID-VkDeviceGroupSubmitInfo-pWaitSemaphoreDeviceIndices-00085# All -- elements of @pWaitSemaphoreDeviceIndices@ and -- @pSignalSemaphoreDeviceIndices@ /must/ be valid device indices -- -- - #VUID-VkDeviceGroupSubmitInfo-pCommandBufferDeviceMasks-00086# All -- elements of @pCommandBufferDeviceMasks@ /must/ be valid device masks -- -- == Valid Usage (Implicit) -- -- - #VUID-VkDeviceGroupSubmitInfo-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO' -- -- - #VUID-VkDeviceGroupSubmitInfo-pWaitSemaphoreDeviceIndices-parameter# -- If @waitSemaphoreCount@ is not @0@, @pWaitSemaphoreDeviceIndices@ -- /must/ be a valid pointer to an array of @waitSemaphoreCount@ -- @uint32_t@ values -- -- - #VUID-VkDeviceGroupSubmitInfo-pCommandBufferDeviceMasks-parameter# -- If @commandBufferCount@ is not @0@, @pCommandBufferDeviceMasks@ -- /must/ be a valid pointer to an array of @commandBufferCount@ -- @uint32_t@ values -- -- - #VUID-VkDeviceGroupSubmitInfo-pSignalSemaphoreDeviceIndices-parameter# -- If @signalSemaphoreCount@ is not @0@, -- @pSignalSemaphoreDeviceIndices@ /must/ be a valid pointer to an -- array of @signalSemaphoreCount@ @uint32_t@ values -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>, -- 'Vulkan.Core10.Enums.StructureType.StructureType' data DeviceGroupSubmitInfo = DeviceGroupSubmitInfo { -- | @pWaitSemaphoreDeviceIndices@ is a pointer to an array of -- @waitSemaphoreCount@ device indices indicating which physical device -- executes the semaphore wait operation in the corresponding element of -- 'Vulkan.Core10.Queue.SubmitInfo'::@pWaitSemaphores@. DeviceGroupSubmitInfo -> Vector ("heapIndex" ::: Word32) waitSemaphoreDeviceIndices :: Vector Word32 , -- | @pCommandBufferDeviceMasks@ is a pointer to an array of -- @commandBufferCount@ device masks indicating which physical devices -- execute the command buffer in the corresponding element of -- 'Vulkan.Core10.Queue.SubmitInfo'::@pCommandBuffers@. A physical device -- executes the command buffer if the corresponding bit is set in the mask. DeviceGroupSubmitInfo -> Vector ("heapIndex" ::: Word32) commandBufferDeviceMasks :: Vector Word32 , -- | @pSignalSemaphoreDeviceIndices@ is a pointer to an array of -- @signalSemaphoreCount@ device indices indicating which physical device -- executes the semaphore signal operation in the corresponding element of -- 'Vulkan.Core10.Queue.SubmitInfo'::@pSignalSemaphores@. DeviceGroupSubmitInfo -> Vector ("heapIndex" ::: Word32) signalSemaphoreDeviceIndices :: Vector Word32 } deriving (Typeable) #if defined(GENERIC_INSTANCES) deriving instance Generic (DeviceGroupSubmitInfo) #endif deriving instance Show DeviceGroupSubmitInfo instance ToCStruct DeviceGroupSubmitInfo where withCStruct :: forall b. DeviceGroupSubmitInfo -> (Ptr DeviceGroupSubmitInfo -> IO b) -> IO b withCStruct DeviceGroupSubmitInfo x Ptr DeviceGroupSubmitInfo -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 64 forall a b. (a -> b) -> a -> b $ \Ptr DeviceGroupSubmitInfo p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr DeviceGroupSubmitInfo p DeviceGroupSubmitInfo x (Ptr DeviceGroupSubmitInfo -> IO b f Ptr DeviceGroupSubmitInfo p) pokeCStruct :: forall b. Ptr DeviceGroupSubmitInfo -> DeviceGroupSubmitInfo -> IO b -> IO b pokeCStruct Ptr DeviceGroupSubmitInfo p DeviceGroupSubmitInfo{Vector ("heapIndex" ::: Word32) signalSemaphoreDeviceIndices :: Vector ("heapIndex" ::: Word32) commandBufferDeviceMasks :: Vector ("heapIndex" ::: Word32) waitSemaphoreDeviceIndices :: Vector ("heapIndex" ::: Word32) $sel:signalSemaphoreDeviceIndices:DeviceGroupSubmitInfo :: DeviceGroupSubmitInfo -> Vector ("heapIndex" ::: Word32) $sel:commandBufferDeviceMasks:DeviceGroupSubmitInfo :: DeviceGroupSubmitInfo -> Vector ("heapIndex" ::: Word32) $sel:waitSemaphoreDeviceIndices:DeviceGroupSubmitInfo :: DeviceGroupSubmitInfo -> Vector ("heapIndex" ::: Word32) ..} IO b f = forall (m :: * -> *) r. Monad m => ContT r m r -> m r evalContT forall a b. (a -> b) -> a -> b $ do forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector ("heapIndex" ::: Word32) waitSemaphoreDeviceIndices)) :: Word32)) Ptr ("heapIndex" ::: Word32) pPWaitSemaphoreDeviceIndices' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Word32 ((forall a. Vector a -> Int Data.Vector.length (Vector ("heapIndex" ::: Word32) waitSemaphoreDeviceIndices)) forall a. Num a => a -> a -> a * Int 4) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i "heapIndex" ::: Word32 e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("heapIndex" ::: Word32) pPWaitSemaphoreDeviceIndices' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 4 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32) ("heapIndex" ::: Word32 e)) (Vector ("heapIndex" ::: Word32) waitSemaphoreDeviceIndices) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr (Ptr Word32))) (Ptr ("heapIndex" ::: Word32) pPWaitSemaphoreDeviceIndices') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector ("heapIndex" ::: Word32) commandBufferDeviceMasks)) :: Word32)) Ptr ("heapIndex" ::: Word32) pPCommandBufferDeviceMasks' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Word32 ((forall a. Vector a -> Int Data.Vector.length (Vector ("heapIndex" ::: Word32) commandBufferDeviceMasks)) forall a. Num a => a -> a -> a * Int 4) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i "heapIndex" ::: Word32 e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("heapIndex" ::: Word32) pPCommandBufferDeviceMasks' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 4 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32) ("heapIndex" ::: Word32 e)) (Vector ("heapIndex" ::: Word32) commandBufferDeviceMasks) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr Word32))) (Ptr ("heapIndex" ::: Word32) pPCommandBufferDeviceMasks') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr Word32)) ((forall a b. (Integral a, Num b) => a -> b fromIntegral (forall a. Vector a -> Int Data.Vector.length forall a b. (a -> b) -> a -> b $ (Vector ("heapIndex" ::: Word32) signalSemaphoreDeviceIndices)) :: Word32)) Ptr ("heapIndex" ::: Word32) pPSignalSemaphoreDeviceIndices' <- forall {k} (r :: k) (m :: k -> *) a. ((a -> m r) -> m r) -> ContT r m a ContT forall a b. (a -> b) -> a -> b $ forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes @Word32 ((forall a. Vector a -> Int Data.Vector.length (Vector ("heapIndex" ::: Word32) signalSemaphoreDeviceIndices)) forall a. Num a => a -> a -> a * Int 4) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall (m :: * -> *) a b. Monad m => (Int -> a -> m b) -> Vector a -> m () Data.Vector.imapM_ (\Int i "heapIndex" ::: Word32 e -> forall a. Storable a => Ptr a -> a -> IO () poke (Ptr ("heapIndex" ::: Word32) pPSignalSemaphoreDeviceIndices' forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 4 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32) ("heapIndex" ::: Word32 e)) (Vector ("heapIndex" ::: Word32) signalSemaphoreDeviceIndices) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr (Ptr Word32))) (Ptr ("heapIndex" ::: Word32) pPSignalSemaphoreDeviceIndices') forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f cStructSize :: Int cStructSize = Int 64 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr DeviceGroupSubmitInfo -> IO b -> IO b pokeZeroCStruct Ptr DeviceGroupSubmitInfo p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_DEVICE_GROUP_SUBMIT_INFO) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) IO b f instance FromCStruct DeviceGroupSubmitInfo where peekCStruct :: Ptr DeviceGroupSubmitInfo -> IO DeviceGroupSubmitInfo peekCStruct Ptr DeviceGroupSubmitInfo p = do "heapIndex" ::: Word32 waitSemaphoreCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) Ptr ("heapIndex" ::: Word32) pWaitSemaphoreDeviceIndices <- forall a. Storable a => Ptr a -> IO a peek @(Ptr Word32) ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr (Ptr Word32))) Vector ("heapIndex" ::: Word32) pWaitSemaphoreDeviceIndices' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral "heapIndex" ::: Word32 waitSemaphoreCount) (\Int i -> forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ("heapIndex" ::: Word32) pWaitSemaphoreDeviceIndices forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 4 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32))) "heapIndex" ::: Word32 commandBufferCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr Word32)) Ptr ("heapIndex" ::: Word32) pCommandBufferDeviceMasks <- forall a. Storable a => Ptr a -> IO a peek @(Ptr Word32) ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 40 :: Ptr (Ptr Word32))) Vector ("heapIndex" ::: Word32) pCommandBufferDeviceMasks' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral "heapIndex" ::: Word32 commandBufferCount) (\Int i -> forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ("heapIndex" ::: Word32) pCommandBufferDeviceMasks forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 4 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32))) "heapIndex" ::: Word32 signalSemaphoreCount <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 48 :: Ptr Word32)) Ptr ("heapIndex" ::: Word32) pSignalSemaphoreDeviceIndices <- forall a. Storable a => Ptr a -> IO a peek @(Ptr Word32) ((Ptr DeviceGroupSubmitInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 56 :: Ptr (Ptr Word32))) Vector ("heapIndex" ::: Word32) pSignalSemaphoreDeviceIndices' <- forall (m :: * -> *) a. Monad m => Int -> (Int -> m a) -> m (Vector a) generateM (forall a b. (Integral a, Num b) => a -> b fromIntegral "heapIndex" ::: Word32 signalSemaphoreCount) (\Int i -> forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr ("heapIndex" ::: Word32) pSignalSemaphoreDeviceIndices forall a. Ptr a -> Int -> Ptr a `advancePtrBytes` (Int 4 forall a. Num a => a -> a -> a * (Int i)) :: Ptr Word32))) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ Vector ("heapIndex" ::: Word32) -> Vector ("heapIndex" ::: Word32) -> Vector ("heapIndex" ::: Word32) -> DeviceGroupSubmitInfo DeviceGroupSubmitInfo Vector ("heapIndex" ::: Word32) pWaitSemaphoreDeviceIndices' Vector ("heapIndex" ::: Word32) pCommandBufferDeviceMasks' Vector ("heapIndex" ::: Word32) pSignalSemaphoreDeviceIndices' instance Zero DeviceGroupSubmitInfo where zero :: DeviceGroupSubmitInfo zero = Vector ("heapIndex" ::: Word32) -> Vector ("heapIndex" ::: Word32) -> Vector ("heapIndex" ::: Word32) -> DeviceGroupSubmitInfo DeviceGroupSubmitInfo forall a. Monoid a => a mempty forall a. Monoid a => a mempty forall a. Monoid a => a mempty -- | VkDeviceGroupBindSparseInfo - Structure indicating which instances are -- bound -- -- = Description -- -- These device indices apply to all buffer and image memory binds included -- in the batch pointing to this structure. The semaphore waits and signals -- for the batch are executed only by the physical device specified by the -- @resourceDeviceIndex@. -- -- If this structure is not present, @resourceDeviceIndex@ and -- @memoryDeviceIndex@ are assumed to be zero. -- -- == Valid Usage -- -- - #VUID-VkDeviceGroupBindSparseInfo-resourceDeviceIndex-01118# -- @resourceDeviceIndex@ and @memoryDeviceIndex@ /must/ both be valid -- device indices -- -- - #VUID-VkDeviceGroupBindSparseInfo-memoryDeviceIndex-01119# Each -- memory allocation bound in this batch /must/ have allocated an -- instance for @memoryDeviceIndex@ -- -- == Valid Usage (Implicit) -- -- - #VUID-VkDeviceGroupBindSparseInfo-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>, -- 'Vulkan.Core10.Enums.StructureType.StructureType' data DeviceGroupBindSparseInfo = DeviceGroupBindSparseInfo { -- | @resourceDeviceIndex@ is a device index indicating which instance of the -- resource is bound. DeviceGroupBindSparseInfo -> "heapIndex" ::: Word32 resourceDeviceIndex :: Word32 , -- | @memoryDeviceIndex@ is a device index indicating which instance of the -- memory the resource instance is bound to. DeviceGroupBindSparseInfo -> "heapIndex" ::: Word32 memoryDeviceIndex :: Word32 } deriving (Typeable, DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool $c/= :: DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool == :: DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool $c== :: DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (DeviceGroupBindSparseInfo) #endif deriving instance Show DeviceGroupBindSparseInfo instance ToCStruct DeviceGroupBindSparseInfo where withCStruct :: forall b. DeviceGroupBindSparseInfo -> (Ptr DeviceGroupBindSparseInfo -> IO b) -> IO b withCStruct DeviceGroupBindSparseInfo x Ptr DeviceGroupBindSparseInfo -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 24 forall a b. (a -> b) -> a -> b $ \Ptr DeviceGroupBindSparseInfo p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr DeviceGroupBindSparseInfo p DeviceGroupBindSparseInfo x (Ptr DeviceGroupBindSparseInfo -> IO b f Ptr DeviceGroupBindSparseInfo p) pokeCStruct :: forall b. Ptr DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> IO b -> IO b pokeCStruct Ptr DeviceGroupBindSparseInfo p DeviceGroupBindSparseInfo{"heapIndex" ::: Word32 memoryDeviceIndex :: "heapIndex" ::: Word32 resourceDeviceIndex :: "heapIndex" ::: Word32 $sel:memoryDeviceIndex:DeviceGroupBindSparseInfo :: DeviceGroupBindSparseInfo -> "heapIndex" ::: Word32 $sel:resourceDeviceIndex:DeviceGroupBindSparseInfo :: DeviceGroupBindSparseInfo -> "heapIndex" ::: Word32 ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) ("heapIndex" ::: Word32 resourceDeviceIndex) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) ("heapIndex" ::: Word32 memoryDeviceIndex) IO b f cStructSize :: Int cStructSize = Int 24 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. Ptr DeviceGroupBindSparseInfo -> IO b -> IO b pokeZeroCStruct Ptr DeviceGroupBindSparseInfo p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_DEVICE_GROUP_BIND_SPARSE_INFO) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) (forall a. Ptr a nullPtr) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) (forall a. Zero a => a zero) IO b f instance FromCStruct DeviceGroupBindSparseInfo where peekCStruct :: Ptr DeviceGroupBindSparseInfo -> IO DeviceGroupBindSparseInfo peekCStruct Ptr DeviceGroupBindSparseInfo p = do "heapIndex" ::: Word32 resourceDeviceIndex <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr Word32)) "heapIndex" ::: Word32 memoryDeviceIndex <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr DeviceGroupBindSparseInfo p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 20 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> DeviceGroupBindSparseInfo DeviceGroupBindSparseInfo "heapIndex" ::: Word32 resourceDeviceIndex "heapIndex" ::: Word32 memoryDeviceIndex instance Storable DeviceGroupBindSparseInfo where sizeOf :: DeviceGroupBindSparseInfo -> Int sizeOf ~DeviceGroupBindSparseInfo _ = Int 24 alignment :: DeviceGroupBindSparseInfo -> Int alignment ~DeviceGroupBindSparseInfo _ = Int 8 peek :: Ptr DeviceGroupBindSparseInfo -> IO DeviceGroupBindSparseInfo peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: Ptr DeviceGroupBindSparseInfo -> DeviceGroupBindSparseInfo -> IO () poke Ptr DeviceGroupBindSparseInfo ptr DeviceGroupBindSparseInfo poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr DeviceGroupBindSparseInfo ptr DeviceGroupBindSparseInfo poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero DeviceGroupBindSparseInfo where zero :: DeviceGroupBindSparseInfo zero = ("heapIndex" ::: Word32) -> ("heapIndex" ::: Word32) -> DeviceGroupBindSparseInfo DeviceGroupBindSparseInfo forall a. Zero a => a zero forall a. Zero a => a zero