{-# language CPP #-} -- No documentation found for Chapter "Memory" module Vulkan.Core10.Memory ( allocateMemory , withMemory , freeMemory , mapMemory , withMappedMemory , unmapMemory , flushMappedMemoryRanges , invalidateMappedMemoryRanges , getDeviceMemoryCommitment , MemoryAllocateInfo(..) , MappedMemoryRange(..) , MemoryMapFlags(..) ) where import Vulkan.Internal.Utils (traceAroundEvent) import Control.Exception.Base (bracket) import Control.Monad (unless) import Control.Monad.IO.Class (liftIO) import Data.Typeable (eqT) import Foreign.Marshal.Alloc (allocaBytes) import Foreign.Marshal.Alloc (callocBytes) import Foreign.Marshal.Alloc (free) import GHC.Base (when) import GHC.IO (throwIO) import GHC.Ptr (castPtr) import GHC.Ptr (nullFunPtr) import Foreign.Ptr (nullPtr) import Foreign.Ptr (plusPtr) import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Cont (evalContT) import 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.Type.Equality ((:~:)(Refl)) import Data.Typeable (Typeable) import Foreign.Storable (Storable) import Foreign.Storable (Storable(peek)) import Foreign.Storable (Storable(poke)) import qualified Foreign.Storable (Storable(..)) import GHC.Generics (Generic) import GHC.IO.Exception (IOErrorType(..)) import GHC.IO.Exception (IOException(..)) import Foreign.Ptr (FunPtr) import Foreign.Ptr (Ptr) import Data.Word (Word32) import Data.Kind (Type) import Control.Monad.Trans.Cont (ContT(..)) import Data.Vector (Vector) import Vulkan.CStruct.Extends (forgetExtensions) import Vulkan.NamedType ((:::)) import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks) import Vulkan.CStruct.Extends (Chain) import {-# SOURCE #-} Vulkan.Extensions.VK_NV_dedicated_allocation (DedicatedAllocationMemoryAllocateInfoNV) import Vulkan.Core10.Handles (Device) import Vulkan.Core10.Handles (Device(..)) import Vulkan.Core10.Handles (Device(Device)) import Vulkan.Dynamic (DeviceCmds(pVkAllocateMemory)) import Vulkan.Dynamic (DeviceCmds(pVkFlushMappedMemoryRanges)) import Vulkan.Dynamic (DeviceCmds(pVkFreeMemory)) import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceMemoryCommitment)) import Vulkan.Dynamic (DeviceCmds(pVkInvalidateMappedMemoryRanges)) import Vulkan.Dynamic (DeviceCmds(pVkMapMemory)) import Vulkan.Dynamic (DeviceCmds(pVkUnmapMemory)) import Vulkan.Core10.Handles (DeviceMemory) import Vulkan.Core10.Handles (DeviceMemory(..)) import Vulkan.Core10.FundamentalTypes (DeviceSize) import Vulkan.Core10.Handles (Device_T) import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_external_memory (ExportMemoryAllocateInfo) import {-# SOURCE #-} Vulkan.Extensions.VK_NV_external_memory (ExportMemoryAllocateInfoNV) import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_external_memory_win32 (ExportMemoryWin32HandleInfoKHR) import {-# SOURCE #-} Vulkan.Extensions.VK_NV_external_memory_win32 (ExportMemoryWin32HandleInfoNV) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_metal_objects (ExportMetalObjectCreateInfoEXT) import Vulkan.CStruct.Extends (Extends) import Vulkan.CStruct.Extends (Extendss) import Vulkan.CStruct.Extends (Extensible(..)) import {-# SOURCE #-} Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer (ImportAndroidHardwareBufferInfoANDROID) import {-# SOURCE #-} Vulkan.Extensions.VK_FUCHSIA_buffer_collection (ImportMemoryBufferCollectionFUCHSIA) import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_external_memory_fd (ImportMemoryFdInfoKHR) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_external_memory_host (ImportMemoryHostPointerInfoEXT) import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_external_memory_win32 (ImportMemoryWin32HandleInfoKHR) import {-# SOURCE #-} Vulkan.Extensions.VK_NV_external_memory_win32 (ImportMemoryWin32HandleInfoNV) import {-# SOURCE #-} Vulkan.Extensions.VK_FUCHSIA_external_memory (ImportMemoryZirconHandleInfoFUCHSIA) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_metal_objects (ImportMetalBufferInfoEXT) import {-# SOURCE #-} Vulkan.Extensions.VK_QNX_external_memory_screen_buffer (ImportScreenBufferInfoQNX) import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_group (MemoryAllocateFlagsInfo) import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation (MemoryDedicatedAllocateInfo) import Vulkan.Core10.Enums.MemoryMapFlags (MemoryMapFlags) import Vulkan.Core10.Enums.MemoryMapFlags (MemoryMapFlags(..)) import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address (MemoryOpaqueCaptureAddressAllocateInfo) import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_memory_priority (MemoryPriorityAllocateInfoEXT) import Vulkan.CStruct.Extends (PeekChain) import Vulkan.CStruct.Extends (PeekChain(..)) import Vulkan.CStruct.Extends (PokeChain) import Vulkan.CStruct.Extends (PokeChain(..)) import Vulkan.Core10.Enums.Result (Result) import Vulkan.Core10.Enums.Result (Result(..)) import Vulkan.CStruct.Extends (SomeStruct) import Vulkan.Core10.Enums.StructureType (StructureType) import Vulkan.Exception (VulkanException(..)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MAPPED_MEMORY_RANGE)) import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO)) import Vulkan.Core10.Enums.Result (Result(SUCCESS)) import Vulkan.Core10.Enums.MemoryMapFlags (MemoryMapFlags(..)) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkAllocateMemory :: FunPtr (Ptr Device_T -> Ptr (SomeStruct MemoryAllocateInfo) -> Ptr AllocationCallbacks -> Ptr DeviceMemory -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct MemoryAllocateInfo) -> Ptr AllocationCallbacks -> Ptr DeviceMemory -> IO Result -- | vkAllocateMemory - Allocate device memory -- -- = Description -- -- Allocations returned by 'allocateMemory' are guaranteed to meet any -- alignment requirement of the implementation. For example, if an -- implementation requires 128 byte alignment for images and 64 byte -- alignment for buffers, the device memory returned through this mechanism -- would be 128-byte aligned. This ensures that applications /can/ -- correctly suballocate objects of different types (with potentially -- different alignment requirements) in the same memory object. -- -- When memory is allocated, its contents are undefined with the following -- constraint: -- -- - The contents of unprotected memory /must/ not be a function of the -- contents of data protected memory objects, even if those memory -- objects were previously freed. -- -- Note -- -- The contents of memory allocated by one application /should/ not be a -- function of data from protected memory objects of another application, -- even if those memory objects were previously freed. -- -- The maximum number of valid memory allocations that /can/ exist -- simultaneously within a 'Vulkan.Core10.Handles.Device' /may/ be -- restricted by implementation- or platform-dependent limits. The -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#limits-maxMemoryAllocationCount maxMemoryAllocationCount> -- feature describes the number of allocations that /can/ exist -- simultaneously before encountering these internal limits. -- -- Note -- -- For historical reasons, if @maxMemoryAllocationCount@ is exceeded, some -- implementations may return -- 'Vulkan.Core10.Enums.Result.ERROR_TOO_MANY_OBJECTS'. Exceeding this -- limit will result in undefined behavior, and an application should not -- rely on the use of the returned error code in order to identify when the -- limit is reached. -- -- Note -- -- Many protected memory implementations involve complex hardware and -- system software support, and often have additional and much lower limits -- on the number of simultaneous protected memory allocations (from memory -- types with the -- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_PROTECTED_BIT' -- property) than for non-protected memory allocations. These limits can be -- system-wide, and depend on a variety of factors outside of the Vulkan -- implementation, so they cannot be queried in Vulkan. Applications -- /should/ use as few allocations as possible from such memory types by -- suballocating aggressively, and be prepared for allocation failure even -- when there is apparently plenty of capacity remaining in the memory -- heap. As a guideline, the Vulkan conformance test suite requires that at -- least 80 minimum-size allocations can exist concurrently when no other -- uses of protected memory are active in the system. -- -- Some platforms /may/ have a limit on the maximum size of a single -- allocation. For example, certain systems /may/ fail to create -- allocations with a size greater than or equal to 4GB. Such a limit is -- implementation-dependent, and if such a failure occurs then the error -- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY' /must/ be -- returned. This limit is advertised in -- 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance3.PhysicalDeviceMaintenance3Properties'::@maxMemoryAllocationSize@. -- -- The cumulative memory size allocated to a heap /can/ be limited by the -- size of the specified heap. In such cases, allocated memory is tracked -- on a per-device and per-heap basis. Some platforms allow overallocation -- into other heaps. The overallocation behavior /can/ be specified through -- the @VK_AMD_memory_overallocation_behavior@ extension. -- -- If the -- 'Vulkan.Extensions.VK_EXT_pageable_device_local_memory.PhysicalDevicePageableDeviceLocalMemoryFeaturesEXT'::@pageableDeviceLocalMemory@ -- feature is enabled, memory allocations made from a heap that includes -- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_DEVICE_LOCAL_BIT' in -- 'Vulkan.Core10.DeviceInitialization.MemoryHeap'::@flags@ /may/ be -- transparently moved to host-local memory allowing multiple applications -- to share device-local memory. If there is no space left in device-local -- memory when this new allocation is made, other allocations /may/ be -- moved out transparently to make room. The operating system will -- determine which allocations to move to device-local memory or host-local -- memory based on platform-specific criteria. To help the operating system -- make good choices, the application /should/ set the appropriate memory -- priority with -- 'Vulkan.Extensions.VK_EXT_memory_priority.MemoryPriorityAllocateInfoEXT' -- and adjust it as necessary with -- 'Vulkan.Extensions.VK_EXT_pageable_device_local_memory.setDeviceMemoryPriorityEXT'. -- Higher priority allocations will moved to device-local memory first. -- -- Memory allocations made on heaps without the -- 'Vulkan.Core10.Enums.MemoryHeapFlagBits.MEMORY_HEAP_DEVICE_LOCAL_BIT' -- property will not be transparently promoted to device-local memory by -- the operating system. -- -- == Valid Usage -- -- - #VUID-vkAllocateMemory-pAllocateInfo-01713# -- @pAllocateInfo->allocationSize@ /must/ be less than or equal to -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceMemoryProperties'::@memoryHeaps@[@memindex@].@size@ -- where @memindex@ = -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceMemoryProperties'::@memoryTypes@[@pAllocateInfo->memoryTypeIndex@].@heapIndex@ -- as returned by -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceMemoryProperties' -- for the 'Vulkan.Core10.Handles.PhysicalDevice' that @device@ was -- created from -- -- - #VUID-vkAllocateMemory-pAllocateInfo-01714# -- @pAllocateInfo->memoryTypeIndex@ /must/ be less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceMemoryProperties'::@memoryTypeCount@ -- as returned by -- 'Vulkan.Core10.DeviceInitialization.getPhysicalDeviceMemoryProperties' -- for the 'Vulkan.Core10.Handles.PhysicalDevice' that @device@ was -- created from -- -- - #VUID-vkAllocateMemory-deviceCoherentMemory-02790# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-deviceCoherentMemory deviceCoherentMemory> -- feature is not enabled, @pAllocateInfo->memoryTypeIndex@ /must/ not -- identify a memory type supporting -- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD' -- -- - #VUID-vkAllocateMemory-maxMemoryAllocationCount-04101# There /must/ -- be less than -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxMemoryAllocationCount@ -- device memory allocations currently allocated on the device -- -- == Valid Usage (Implicit) -- -- - #VUID-vkAllocateMemory-device-parameter# @device@ /must/ be a valid -- 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkAllocateMemory-pAllocateInfo-parameter# @pAllocateInfo@ -- /must/ be a valid pointer to a valid 'MemoryAllocateInfo' structure -- -- - #VUID-vkAllocateMemory-pAllocator-parameter# If @pAllocator@ is not -- @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkAllocateMemory-pMemory-parameter# @pMemory@ /must/ be a -- valid pointer to a 'Vulkan.Core10.Handles.DeviceMemory' handle -- -- == Return Codes -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>] -- -- - 'Vulkan.Core10.Enums.Result.SUCCESS' -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>] -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY' -- -- - 'Vulkan.Core10.Enums.Result.ERROR_INVALID_EXTERNAL_HANDLE' -- -- - 'Vulkan.Extensions.VK_KHR_buffer_device_address.ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS_KHR' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.DeviceMemory', -- 'MemoryAllocateInfo' allocateMemory :: forall a io . (Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) => -- | @device@ is the logical device that owns the memory. Device -> -- | @pAllocateInfo@ is a pointer to a 'MemoryAllocateInfo' structure -- describing parameters of the allocation. A successfully returned -- allocation /must/ use the requested parameters — no substitution is -- permitted by the implementation. (MemoryAllocateInfo a) -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io (DeviceMemory) allocateMemory :: forall (a :: [*]) (io :: * -> *). (Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) => Device -> MemoryAllocateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io DeviceMemory allocateMemory Device device MemoryAllocateInfo a allocateInfo "allocator" ::: Maybe AllocationCallbacks allocator = 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 vkAllocateMemoryPtr :: FunPtr (Ptr Device_T -> ("pAllocateInfo" ::: Ptr (SomeStruct MemoryAllocateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pMemory" ::: Ptr DeviceMemory) -> IO Result) vkAllocateMemoryPtr = DeviceCmds -> FunPtr (Ptr Device_T -> ("pAllocateInfo" ::: Ptr (SomeStruct MemoryAllocateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pMemory" ::: Ptr DeviceMemory) -> IO Result) pVkAllocateMemory (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 -> ("pAllocateInfo" ::: Ptr (SomeStruct MemoryAllocateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pMemory" ::: Ptr DeviceMemory) -> IO Result) vkAllocateMemoryPtr 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 vkAllocateMemory is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkAllocateMemory' :: Ptr Device_T -> ("pAllocateInfo" ::: Ptr (SomeStruct MemoryAllocateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pMemory" ::: Ptr DeviceMemory) -> IO Result vkAllocateMemory' = FunPtr (Ptr Device_T -> ("pAllocateInfo" ::: Ptr (SomeStruct MemoryAllocateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pMemory" ::: Ptr DeviceMemory) -> IO Result) -> Ptr Device_T -> ("pAllocateInfo" ::: Ptr (SomeStruct MemoryAllocateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pMemory" ::: Ptr DeviceMemory) -> IO Result mkVkAllocateMemory FunPtr (Ptr Device_T -> ("pAllocateInfo" ::: Ptr (SomeStruct MemoryAllocateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pMemory" ::: Ptr DeviceMemory) -> IO Result) vkAllocateMemoryPtr Ptr (MemoryAllocateInfo a) pAllocateInfo <- 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. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (MemoryAllocateInfo a allocateInfo) "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> 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. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (AllocationCallbacks j) "pMemory" ::: Ptr DeviceMemory pPMemory <- 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 @DeviceMemory Int 8) forall a. Ptr a -> IO () free Result r <- 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 "vkAllocateMemory" (Ptr Device_T -> ("pAllocateInfo" ::: Ptr (SomeStruct MemoryAllocateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pMemory" ::: Ptr DeviceMemory) -> IO Result vkAllocateMemory' (Device -> Ptr Device_T deviceHandle (Device device)) (forall (a :: [*] -> *) (es :: [*]). Ptr (a es) -> Ptr (SomeStruct a) forgetExtensions Ptr (MemoryAllocateInfo a) pAllocateInfo) "pAllocator" ::: Ptr AllocationCallbacks pAllocator ("pMemory" ::: Ptr DeviceMemory pPMemory)) 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 () when (Result r forall a. Ord a => a -> a -> Bool < Result SUCCESS) (forall e a. Exception e => e -> IO a throwIO (Result -> VulkanException VulkanException Result r)) DeviceMemory pMemory <- 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 @DeviceMemory "pMemory" ::: Ptr DeviceMemory pPMemory forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ (DeviceMemory pMemory) -- | A convenience wrapper to make a compatible pair of calls to -- 'allocateMemory' and 'freeMemory' -- -- To ensure that 'freeMemory' is always called: pass -- 'Control.Exception.bracket' (or the allocate function from your -- favourite resource management library) as the last argument. -- To just extract the pair pass '(,)' as the last argument. -- withMemory :: forall a io r . (Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) => Device -> MemoryAllocateInfo a -> Maybe AllocationCallbacks -> (io DeviceMemory -> (DeviceMemory -> io ()) -> r) -> r withMemory :: forall (a :: [*]) (io :: * -> *) r. (Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) => Device -> MemoryAllocateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> (io DeviceMemory -> (DeviceMemory -> io ()) -> r) -> r withMemory Device device MemoryAllocateInfo a pAllocateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator io DeviceMemory -> (DeviceMemory -> io ()) -> r b = io DeviceMemory -> (DeviceMemory -> io ()) -> r b (forall (a :: [*]) (io :: * -> *). (Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) => Device -> MemoryAllocateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io DeviceMemory allocateMemory Device device MemoryAllocateInfo a pAllocateInfo "allocator" ::: Maybe AllocationCallbacks pAllocator) (\(DeviceMemory o0) -> forall (io :: * -> *). MonadIO io => Device -> DeviceMemory -> ("allocator" ::: Maybe AllocationCallbacks) -> io () freeMemory Device device DeviceMemory o0 "allocator" ::: Maybe AllocationCallbacks pAllocator) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkFreeMemory :: FunPtr (Ptr Device_T -> DeviceMemory -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> DeviceMemory -> Ptr AllocationCallbacks -> IO () -- | vkFreeMemory - Free device memory -- -- = Description -- -- Before freeing a memory object, an application /must/ ensure the memory -- object is no longer in use by the device — for example by command -- buffers in the /pending state/. Memory /can/ be freed whilst still bound -- to resources, but those resources /must/ not be used afterwards. Freeing -- a memory object releases the reference it held, if any, to its payload. -- If there are still any bound images or buffers, the memory object’s -- payload /may/ not be immediately released by the implementation, but -- /must/ be released by the time all bound images and buffers have been -- destroyed. Once all references to a payload are released, it is returned -- to the heap from which it was allocated. -- -- How memory objects are bound to Images and Buffers is described in -- detail in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#resources-association Resource Memory Association> -- section. -- -- If a memory object is mapped at the time it is freed, it is implicitly -- unmapped. -- -- Note -- -- As described -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-device-unmap-does-not-flush below>, -- host writes are not implicitly flushed when the memory object is -- unmapped, but the implementation /must/ guarantee that writes that have -- not been flushed do not affect any other memory. -- -- == Valid Usage -- -- - #VUID-vkFreeMemory-memory-00677# All submitted commands that refer -- to @memory@ (via images or buffers) /must/ have completed execution -- -- == Valid Usage (Implicit) -- -- - #VUID-vkFreeMemory-device-parameter# @device@ /must/ be a valid -- 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkFreeMemory-memory-parameter# If @memory@ is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', @memory@ /must/ be a valid -- 'Vulkan.Core10.Handles.DeviceMemory' handle -- -- - #VUID-vkFreeMemory-pAllocator-parameter# If @pAllocator@ is not -- @NULL@, @pAllocator@ /must/ be a valid pointer to a valid -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure -- -- - #VUID-vkFreeMemory-memory-parent# If @memory@ is a valid handle, it -- /must/ have been created, allocated, or retrieved from @device@ -- -- == Host Synchronization -- -- - Host access to @memory@ /must/ be externally synchronized -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks', -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.DeviceMemory' freeMemory :: forall io . (MonadIO io) => -- | @device@ is the logical device that owns the memory. Device -> -- | @memory@ is the 'Vulkan.Core10.Handles.DeviceMemory' object to be freed. DeviceMemory -> -- | @pAllocator@ controls host memory allocation as described in the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation> -- chapter. ("allocator" ::: Maybe AllocationCallbacks) -> io () freeMemory :: forall (io :: * -> *). MonadIO io => Device -> DeviceMemory -> ("allocator" ::: Maybe AllocationCallbacks) -> io () freeMemory Device device DeviceMemory memory "allocator" ::: Maybe AllocationCallbacks allocator = 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 vkFreeMemoryPtr :: FunPtr (Ptr Device_T -> DeviceMemory -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkFreeMemoryPtr = DeviceCmds -> FunPtr (Ptr Device_T -> DeviceMemory -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) pVkFreeMemory (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> 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 -> DeviceMemory -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkFreeMemoryPtr 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 vkFreeMemory is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkFreeMemory' :: Ptr Device_T -> DeviceMemory -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkFreeMemory' = FunPtr (Ptr Device_T -> DeviceMemory -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> Ptr Device_T -> DeviceMemory -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () mkVkFreeMemory FunPtr (Ptr Device_T -> DeviceMemory -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) vkFreeMemoryPtr "pAllocator" ::: Ptr AllocationCallbacks pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks allocator) of "allocator" ::: Maybe AllocationCallbacks Nothing -> forall (f :: * -> *) a. Applicative f => a -> f a pure forall a. Ptr a nullPtr Just AllocationCallbacks j -> 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. ToCStruct a => a -> (Ptr a -> IO b) -> IO b withCStruct (AllocationCallbacks j) 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 "vkFreeMemory" (Ptr Device_T -> DeviceMemory -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO () vkFreeMemory' (Device -> Ptr Device_T deviceHandle (Device device)) (DeviceMemory memory) "pAllocator" ::: Ptr AllocationCallbacks pAllocator) 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" mkVkMapMemory :: FunPtr (Ptr Device_T -> DeviceMemory -> DeviceSize -> DeviceSize -> MemoryMapFlags -> Ptr (Ptr ()) -> IO Result) -> Ptr Device_T -> DeviceMemory -> DeviceSize -> DeviceSize -> MemoryMapFlags -> Ptr (Ptr ()) -> IO Result -- | vkMapMemory - Map a memory object into application address space -- -- = Description -- -- After a successful call to 'mapMemory' the memory object @memory@ is -- considered to be currently /host mapped/. -- -- Note -- -- It is an application error to call 'mapMemory' on a memory object that -- is already /host mapped/. -- -- Note -- -- 'mapMemory' will fail if the implementation is unable to allocate an -- appropriately sized contiguous virtual address range, e.g. due to -- virtual address space fragmentation or platform limits. In such cases, -- 'mapMemory' /must/ return -- 'Vulkan.Core10.Enums.Result.ERROR_MEMORY_MAP_FAILED'. The application -- /can/ improve the likelihood of success by reducing the size of the -- mapped range and\/or removing unneeded mappings using 'unmapMemory'. -- -- 'mapMemory' does not check whether the device memory is currently in use -- before returning the host-accessible pointer. The application /must/ -- guarantee that any previously submitted command that writes to this -- range has completed before the host reads from or writes to that range, -- and that any previously submitted command that reads from that range has -- completed before the host writes to that region (see -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-submission-host-writes here> -- for details on fulfilling such a guarantee). If the device memory was -- allocated without the -- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_COHERENT_BIT' -- set, these guarantees /must/ be made for an extended range: the -- application /must/ round down the start of the range to the nearest -- multiple of -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@nonCoherentAtomSize@, -- and round the end of the range up to the nearest multiple of -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@nonCoherentAtomSize@. -- -- While a range of device memory is host mapped, the application is -- responsible for synchronizing both device and host access to that memory -- range. -- -- Note -- -- It is important for the application developer to become meticulously -- familiar with all of the mechanisms described in the chapter on -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization Synchronization and Cache Control> -- as they are crucial to maintaining memory access ordering. -- -- Calling 'mapMemory' is equivalent to calling -- 'Vulkan.Extensions.VK_KHR_map_memory2.mapMemory2KHR' with an empty -- @pNext@ chain. -- -- == Valid Usage -- -- - #VUID-vkMapMemory-memory-00678# @memory@ /must/ not be currently -- host mapped -- -- - #VUID-vkMapMemory-offset-00679# @offset@ /must/ be less than the -- size of @memory@ -- -- - #VUID-vkMapMemory-size-00680# If @size@ is not equal to -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE', @size@ /must/ be greater -- than @0@ -- -- - #VUID-vkMapMemory-size-00681# If @size@ is not equal to -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE', @size@ /must/ be less than -- or equal to the size of the @memory@ minus @offset@ -- -- - #VUID-vkMapMemory-memory-00682# @memory@ /must/ have been created -- with a memory type that reports -- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_HOST_VISIBLE_BIT' -- -- - #VUID-vkMapMemory-memory-00683# @memory@ /must/ not have been -- allocated with multiple instances -- -- == Valid Usage (Implicit) -- -- - #VUID-vkMapMemory-device-parameter# @device@ /must/ be a valid -- 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkMapMemory-memory-parameter# @memory@ /must/ be a valid -- 'Vulkan.Core10.Handles.DeviceMemory' handle -- -- - #VUID-vkMapMemory-flags-zerobitmask# @flags@ /must/ be @0@ -- -- - #VUID-vkMapMemory-ppData-parameter# @ppData@ /must/ be a valid -- pointer to a pointer value -- -- - #VUID-vkMapMemory-memory-parent# @memory@ /must/ have been created, -- allocated, or retrieved from @device@ -- -- == Host Synchronization -- -- - Host access to @memory@ /must/ be externally synchronized -- -- == Return Codes -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>] -- -- - 'Vulkan.Core10.Enums.Result.SUCCESS' -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>] -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY' -- -- - 'Vulkan.Core10.Enums.Result.ERROR_MEMORY_MAP_FAILED' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.DeviceMemory', -- 'Vulkan.Core10.FundamentalTypes.DeviceSize', -- 'Vulkan.Core10.Enums.MemoryMapFlags.MemoryMapFlags' mapMemory :: forall io . (MonadIO io) => -- | @device@ is the logical device that owns the memory. Device -> -- | @memory@ is the 'Vulkan.Core10.Handles.DeviceMemory' object to be -- mapped. DeviceMemory -> -- | @offset@ is a zero-based byte offset from the beginning of the memory -- object. ("offset" ::: DeviceSize) -> -- | @size@ is the size of the memory range to map, or -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE' to map from @offset@ to the end -- of the allocation. DeviceSize -> -- | @flags@ is reserved for future use. MemoryMapFlags -> io (("data" ::: Ptr ())) mapMemory :: forall (io :: * -> *). MonadIO io => Device -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> io ("data" ::: Ptr ()) mapMemory Device device DeviceMemory memory "offset" ::: DeviceSize offset "offset" ::: DeviceSize size MemoryMapFlags flags = 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 vkMapMemoryPtr :: FunPtr (Ptr Device_T -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO Result) vkMapMemoryPtr = DeviceCmds -> FunPtr (Ptr Device_T -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO Result) pVkMapMemory (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> 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 -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO Result) vkMapMemoryPtr 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 vkMapMemory is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkMapMemory' :: Ptr Device_T -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO Result vkMapMemory' = FunPtr (Ptr Device_T -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO Result) -> Ptr Device_T -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO Result mkVkMapMemory FunPtr (Ptr Device_T -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO Result) vkMapMemoryPtr "ppData" ::: Ptr ("data" ::: Ptr ()) pPpData <- 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 @(Ptr ()) Int 8) forall a. Ptr a -> IO () free Result r <- 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 "vkMapMemory" (Ptr Device_T -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO Result vkMapMemory' (Device -> Ptr Device_T deviceHandle (Device device)) (DeviceMemory memory) ("offset" ::: DeviceSize offset) ("offset" ::: DeviceSize size) (MemoryMapFlags flags) ("ppData" ::: Ptr ("data" ::: Ptr ()) pPpData)) 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 () when (Result r forall a. Ord a => a -> a -> Bool < Result SUCCESS) (forall e a. Exception e => e -> IO a throwIO (Result -> VulkanException VulkanException Result r)) "data" ::: Ptr () ppData <- 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 @(Ptr ()) "ppData" ::: Ptr ("data" ::: Ptr ()) pPpData forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("data" ::: Ptr () ppData) -- | A convenience wrapper to make a compatible pair of calls to 'mapMemory' -- and 'unmapMemory' -- -- To ensure that 'unmapMemory' is always called: pass -- 'Control.Exception.bracket' (or the allocate function from your -- favourite resource management library) as the last argument. -- To just extract the pair pass '(,)' as the last argument. -- withMappedMemory :: forall io r . MonadIO io => Device -> DeviceMemory -> DeviceSize -> DeviceSize -> MemoryMapFlags -> (io (Ptr ()) -> (Ptr () -> io ()) -> r) -> r withMappedMemory :: forall (io :: * -> *) r. MonadIO io => Device -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> (io ("data" ::: Ptr ()) -> (("data" ::: Ptr ()) -> io ()) -> r) -> r withMappedMemory Device device DeviceMemory memory "offset" ::: DeviceSize offset "offset" ::: DeviceSize size MemoryMapFlags flags io ("data" ::: Ptr ()) -> (("data" ::: Ptr ()) -> io ()) -> r b = io ("data" ::: Ptr ()) -> (("data" ::: Ptr ()) -> io ()) -> r b (forall (io :: * -> *). MonadIO io => Device -> DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MemoryMapFlags -> io ("data" ::: Ptr ()) mapMemory Device device DeviceMemory memory "offset" ::: DeviceSize offset "offset" ::: DeviceSize size MemoryMapFlags flags) (\("data" ::: Ptr () _) -> forall (io :: * -> *). MonadIO io => Device -> DeviceMemory -> io () unmapMemory Device device DeviceMemory memory) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkUnmapMemory :: FunPtr (Ptr Device_T -> DeviceMemory -> IO ()) -> Ptr Device_T -> DeviceMemory -> IO () -- | vkUnmapMemory - Unmap a previously mapped memory object -- -- = Description -- -- Calling 'unmapMemory' is equivalent to calling -- 'Vulkan.Extensions.VK_KHR_map_memory2.unmapMemory2KHR' with an empty -- @pNext@ chain and the flags parameter set to zero. -- -- == Valid Usage -- -- - #VUID-vkUnmapMemory-memory-00689# @memory@ /must/ be currently host -- mapped -- -- == Valid Usage (Implicit) -- -- - #VUID-vkUnmapMemory-device-parameter# @device@ /must/ be a valid -- 'Vulkan.Core10.Handles.Device' handle -- -- - #VUID-vkUnmapMemory-memory-parameter# @memory@ /must/ be a valid -- 'Vulkan.Core10.Handles.DeviceMemory' handle -- -- - #VUID-vkUnmapMemory-memory-parent# @memory@ /must/ have been -- created, allocated, or retrieved from @device@ -- -- == Host Synchronization -- -- - Host access to @memory@ /must/ be externally synchronized -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.DeviceMemory' unmapMemory :: forall io . (MonadIO io) => -- | @device@ is the logical device that owns the memory. Device -> -- | @memory@ is the memory object to be unmapped. DeviceMemory -> io () unmapMemory :: forall (io :: * -> *). MonadIO io => Device -> DeviceMemory -> io () unmapMemory Device device DeviceMemory memory = forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO forall a b. (a -> b) -> a -> b $ do let vkUnmapMemoryPtr :: FunPtr (Ptr Device_T -> DeviceMemory -> IO ()) vkUnmapMemoryPtr = DeviceCmds -> FunPtr (Ptr Device_T -> DeviceMemory -> IO ()) pVkUnmapMemory (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> DeviceCmds deviceCmds} -> DeviceCmds deviceCmds) forall (f :: * -> *). Applicative f => Bool -> f () -> f () unless (FunPtr (Ptr Device_T -> DeviceMemory -> IO ()) vkUnmapMemoryPtr 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 vkUnmapMemory is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkUnmapMemory' :: Ptr Device_T -> DeviceMemory -> IO () vkUnmapMemory' = FunPtr (Ptr Device_T -> DeviceMemory -> IO ()) -> Ptr Device_T -> DeviceMemory -> IO () mkVkUnmapMemory FunPtr (Ptr Device_T -> DeviceMemory -> IO ()) vkUnmapMemoryPtr forall a. String -> IO a -> IO a traceAroundEvent String "vkUnmapMemory" (Ptr Device_T -> DeviceMemory -> IO () vkUnmapMemory' (Device -> Ptr Device_T deviceHandle (Device device)) (DeviceMemory memory)) 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" mkVkFlushMappedMemoryRanges :: FunPtr (Ptr Device_T -> Word32 -> Ptr MappedMemoryRange -> IO Result) -> Ptr Device_T -> Word32 -> Ptr MappedMemoryRange -> IO Result -- | vkFlushMappedMemoryRanges - Flush mapped memory ranges -- -- = Description -- -- 'flushMappedMemoryRanges' guarantees that host writes to the memory -- ranges described by @pMemoryRanges@ are made available to the host -- memory domain, such that they /can/ be made available to the device -- memory domain via -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies-available-and-visible memory domain operations> -- using the 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_HOST_WRITE_BIT' -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types access type>. -- -- Within each range described by @pMemoryRanges@, each set of -- @nonCoherentAtomSize@ bytes in that range is flushed if any byte in that -- set has been written by the host since it was first host mapped, or the -- last time it was flushed. If @pMemoryRanges@ includes sets of -- @nonCoherentAtomSize@ bytes where no bytes have been written by the -- host, those bytes /must/ not be flushed. -- -- Unmapping non-coherent memory does not implicitly flush the host mapped -- memory, and host writes that have not been flushed /may/ not ever be -- visible to the device. However, implementations /must/ ensure that -- writes that have not been flushed do not become visible to any other -- memory. -- -- Note -- -- The above guarantee avoids a potential memory corruption in scenarios -- where host writes to a mapped memory object have not been flushed before -- the memory is unmapped (or freed), and the virtual address range is -- subsequently reused for a different mapping (or memory allocation). -- -- == Return Codes -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>] -- -- - 'Vulkan.Core10.Enums.Result.SUCCESS' -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>] -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.Device', 'MappedMemoryRange' flushMappedMemoryRanges :: forall io . (MonadIO io) => -- | @device@ is the logical device that owns the memory ranges. -- -- #VUID-vkFlushMappedMemoryRanges-device-parameter# @device@ /must/ be a -- valid 'Vulkan.Core10.Handles.Device' handle Device -> -- | @pMemoryRanges@ is a pointer to an array of 'MappedMemoryRange' -- structures describing the memory ranges to flush. -- -- #VUID-vkFlushMappedMemoryRanges-pMemoryRanges-parameter# @pMemoryRanges@ -- /must/ be a valid pointer to an array of @memoryRangeCount@ valid -- 'MappedMemoryRange' structures ("memoryRanges" ::: Vector MappedMemoryRange) -> io () flushMappedMemoryRanges :: forall (io :: * -> *). MonadIO io => Device -> ("memoryRanges" ::: Vector MappedMemoryRange) -> io () flushMappedMemoryRanges Device device "memoryRanges" ::: Vector MappedMemoryRange memoryRanges = 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 vkFlushMappedMemoryRangesPtr :: FunPtr (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) vkFlushMappedMemoryRangesPtr = DeviceCmds -> FunPtr (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) pVkFlushMappedMemoryRanges (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> 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 -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) vkFlushMappedMemoryRangesPtr 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 vkFlushMappedMemoryRanges is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkFlushMappedMemoryRanges' :: Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result vkFlushMappedMemoryRanges' = FunPtr (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) -> Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result mkVkFlushMappedMemoryRanges FunPtr (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) vkFlushMappedMemoryRangesPtr "pMemoryRanges" ::: Ptr MappedMemoryRange pPMemoryRanges <- 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 @MappedMemoryRange ((forall a. Vector a -> Int Data.Vector.length ("memoryRanges" ::: Vector MappedMemoryRange memoryRanges)) forall a. Num a => a -> a -> a * Int 40) 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 MappedMemoryRange e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pMemoryRanges" ::: Ptr MappedMemoryRange pPMemoryRanges forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 40 forall a. Num a => a -> a -> a * (Int i)) :: Ptr MappedMemoryRange) (MappedMemoryRange e)) ("memoryRanges" ::: Vector MappedMemoryRange memoryRanges) Result r <- 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 "vkFlushMappedMemoryRanges" (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result vkFlushMappedMemoryRanges' (Device -> Ptr Device_T deviceHandle (Device device)) ((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 $ ("memoryRanges" ::: Vector MappedMemoryRange memoryRanges)) :: Word32)) ("pMemoryRanges" ::: Ptr MappedMemoryRange pPMemoryRanges)) 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 () when (Result r forall a. Ord a => a -> a -> Bool < Result SUCCESS) (forall e a. Exception e => e -> IO a throwIO (Result -> VulkanException VulkanException Result r)) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkInvalidateMappedMemoryRanges :: FunPtr (Ptr Device_T -> Word32 -> Ptr MappedMemoryRange -> IO Result) -> Ptr Device_T -> Word32 -> Ptr MappedMemoryRange -> IO Result -- | vkInvalidateMappedMemoryRanges - Invalidate ranges of mapped memory -- objects -- -- = Description -- -- 'invalidateMappedMemoryRanges' guarantees that device writes to the -- memory ranges described by @pMemoryRanges@, which have been made -- available to the host memory domain using the -- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_HOST_WRITE_BIT' and -- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_HOST_READ_BIT' -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types access types>, -- are made visible to the host. If a range of non-coherent memory is -- written by the host and then invalidated without first being flushed, -- its contents are undefined. -- -- Within each range described by @pMemoryRanges@, each set of -- @nonCoherentAtomSize@ bytes in that range is invalidated if any byte in -- that set has been written by the device since it was first host mapped, -- or the last time it was invalidated. -- -- Note -- -- Mapping non-coherent memory does not implicitly invalidate that memory. -- -- == Return Codes -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>] -- -- - 'Vulkan.Core10.Enums.Result.SUCCESS' -- -- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>] -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' -- -- - 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.Device', 'MappedMemoryRange' invalidateMappedMemoryRanges :: forall io . (MonadIO io) => -- | @device@ is the logical device that owns the memory ranges. -- -- #VUID-vkInvalidateMappedMemoryRanges-device-parameter# @device@ /must/ -- be a valid 'Vulkan.Core10.Handles.Device' handle Device -> -- | @pMemoryRanges@ is a pointer to an array of 'MappedMemoryRange' -- structures describing the memory ranges to invalidate. -- -- #VUID-vkInvalidateMappedMemoryRanges-pMemoryRanges-parameter# -- @pMemoryRanges@ /must/ be a valid pointer to an array of -- @memoryRangeCount@ valid 'MappedMemoryRange' structures ("memoryRanges" ::: Vector MappedMemoryRange) -> io () invalidateMappedMemoryRanges :: forall (io :: * -> *). MonadIO io => Device -> ("memoryRanges" ::: Vector MappedMemoryRange) -> io () invalidateMappedMemoryRanges Device device "memoryRanges" ::: Vector MappedMemoryRange memoryRanges = 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 vkInvalidateMappedMemoryRangesPtr :: FunPtr (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) vkInvalidateMappedMemoryRangesPtr = DeviceCmds -> FunPtr (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) pVkInvalidateMappedMemoryRanges (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> 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 -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) vkInvalidateMappedMemoryRangesPtr 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 vkInvalidateMappedMemoryRanges is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkInvalidateMappedMemoryRanges' :: Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result vkInvalidateMappedMemoryRanges' = FunPtr (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) -> Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result mkVkInvalidateMappedMemoryRanges FunPtr (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result) vkInvalidateMappedMemoryRangesPtr "pMemoryRanges" ::: Ptr MappedMemoryRange pPMemoryRanges <- 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 @MappedMemoryRange ((forall a. Vector a -> Int Data.Vector.length ("memoryRanges" ::: Vector MappedMemoryRange memoryRanges)) forall a. Num a => a -> a -> a * Int 40) 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 MappedMemoryRange e -> forall a. Storable a => Ptr a -> a -> IO () poke ("pMemoryRanges" ::: Ptr MappedMemoryRange pPMemoryRanges forall a b. Ptr a -> Int -> Ptr b `plusPtr` (Int 40 forall a. Num a => a -> a -> a * (Int i)) :: Ptr MappedMemoryRange) (MappedMemoryRange e)) ("memoryRanges" ::: Vector MappedMemoryRange memoryRanges) Result r <- 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 "vkInvalidateMappedMemoryRanges" (Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result vkInvalidateMappedMemoryRanges' (Device -> Ptr Device_T deviceHandle (Device device)) ((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 $ ("memoryRanges" ::: Vector MappedMemoryRange memoryRanges)) :: Word32)) ("pMemoryRanges" ::: Ptr MappedMemoryRange pPMemoryRanges)) 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 () when (Result r forall a. Ord a => a -> a -> Bool < Result SUCCESS) (forall e a. Exception e => e -> IO a throwIO (Result -> VulkanException VulkanException Result r)) foreign import ccall #if !defined(SAFE_FOREIGN_CALLS) unsafe #endif "dynamic" mkVkGetDeviceMemoryCommitment :: FunPtr (Ptr Device_T -> DeviceMemory -> Ptr DeviceSize -> IO ()) -> Ptr Device_T -> DeviceMemory -> Ptr DeviceSize -> IO () -- | vkGetDeviceMemoryCommitment - Query the current commitment for a -- VkDeviceMemory -- -- = Description -- -- The implementation /may/ update the commitment at any time, and the -- value returned by this query /may/ be out of date. -- -- The implementation guarantees to allocate any committed memory from the -- @heapIndex@ indicated by the memory type that the memory object was -- created with. -- -- == Valid Usage (Implicit) -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.DeviceMemory', -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' getDeviceMemoryCommitment :: forall io . (MonadIO io) => -- | @device@ is the logical device that owns the memory. -- -- #VUID-vkGetDeviceMemoryCommitment-device-parameter# @device@ /must/ be a -- valid 'Vulkan.Core10.Handles.Device' handle Device -> -- | @memory@ is the memory object being queried. -- -- #VUID-vkGetDeviceMemoryCommitment-memory-00690# @memory@ /must/ have -- been created with a memory type that reports -- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT' -- -- #VUID-vkGetDeviceMemoryCommitment-memory-parameter# @memory@ /must/ be a -- valid 'Vulkan.Core10.Handles.DeviceMemory' handle -- -- #VUID-vkGetDeviceMemoryCommitment-memory-parent# @memory@ /must/ have -- been created, allocated, or retrieved from @device@ DeviceMemory -> io (("committedMemoryInBytes" ::: DeviceSize)) getDeviceMemoryCommitment :: forall (io :: * -> *). MonadIO io => Device -> DeviceMemory -> io ("offset" ::: DeviceSize) getDeviceMemoryCommitment Device device DeviceMemory memory = 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 vkGetDeviceMemoryCommitmentPtr :: FunPtr (Ptr Device_T -> DeviceMemory -> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) vkGetDeviceMemoryCommitmentPtr = DeviceCmds -> FunPtr (Ptr Device_T -> DeviceMemory -> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) pVkGetDeviceMemoryCommitment (case Device device of Device{DeviceCmds deviceCmds :: DeviceCmds $sel:deviceCmds:Device :: Device -> 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 -> DeviceMemory -> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) vkGetDeviceMemoryCommitmentPtr 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 vkGetDeviceMemoryCommitment is null" forall a. Maybe a Nothing forall a. Maybe a Nothing let vkGetDeviceMemoryCommitment' :: Ptr Device_T -> DeviceMemory -> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)) -> IO () vkGetDeviceMemoryCommitment' = FunPtr (Ptr Device_T -> DeviceMemory -> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) -> Ptr Device_T -> DeviceMemory -> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)) -> IO () mkVkGetDeviceMemoryCommitment FunPtr (Ptr Device_T -> DeviceMemory -> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)) -> IO ()) vkGetDeviceMemoryCommitmentPtr "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize) pPCommittedMemoryInBytes <- 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 @DeviceSize Int 8) 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 "vkGetDeviceMemoryCommitment" (Ptr Device_T -> DeviceMemory -> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)) -> IO () vkGetDeviceMemoryCommitment' (Device -> Ptr Device_T deviceHandle (Device device)) (DeviceMemory memory) ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize) pPCommittedMemoryInBytes)) "offset" ::: DeviceSize pCommittedMemoryInBytes <- 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 @DeviceSize "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize) pPCommittedMemoryInBytes forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ ("offset" ::: DeviceSize pCommittedMemoryInBytes) -- | VkMemoryAllocateInfo - Structure containing parameters of a memory -- allocation -- -- = Description -- -- The internal data of an allocated device memory object /must/ include a -- reference to implementation-specific resources, referred to as the -- memory object’s /payload/. Applications /can/ also import and export -- that internal data to and from device memory objects to share data -- between Vulkan instances and other compatible APIs. A -- 'MemoryAllocateInfo' structure defines a memory import operation if its -- @pNext@ chain includes one of the following structures: -- -- - 'Vulkan.Extensions.VK_KHR_external_memory_win32.ImportMemoryWin32HandleInfoKHR' -- with a non-zero @handleType@ value -- -- - 'Vulkan.Extensions.VK_KHR_external_memory_fd.ImportMemoryFdInfoKHR' -- with a non-zero @handleType@ value -- -- - 'Vulkan.Extensions.VK_EXT_external_memory_host.ImportMemoryHostPointerInfoEXT' -- with a non-zero @handleType@ value -- -- - 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ImportAndroidHardwareBufferInfoANDROID' -- with a non-@NULL@ @buffer@ value -- -- - 'Vulkan.Extensions.VK_FUCHSIA_external_memory.ImportMemoryZirconHandleInfoFUCHSIA' -- with a non-zero @handleType@ value -- -- - 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.ImportMemoryBufferCollectionFUCHSIA' -- -- - 'Vulkan.Extensions.VK_QNX_external_memory_screen_buffer.ImportScreenBufferInfoQNX' -- with a non-@NULL@ @buffer@ value -- -- If the parameters define an import operation and the external handle -- type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_D3D11_TEXTURE_BIT', -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_D3D11_TEXTURE_KMT_BIT', -- or -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_D3D12_RESOURCE_BIT', -- @allocationSize@ is ignored. The implementation /must/ query the size of -- these allocations from the OS. -- -- Whether device memory objects constructed via a memory import operation -- hold a reference to their payload depends on the properties of the -- handle type used to perform the import, as defined below for each valid -- handle type. Importing memory /must/ not modify the content of the -- memory. Implementations /must/ ensure that importing memory does not -- enable the importing Vulkan instance to access any memory or resources -- in other Vulkan instances other than that corresponding to the memory -- object imported. Implementations /must/ also ensure accessing imported -- memory which has not been initialized does not allow the importing -- Vulkan instance to obtain data from the exporting Vulkan instance or -- vice-versa. -- -- Note -- -- How exported and imported memory is isolated is left to the -- implementation, but applications should be aware that such isolation -- /may/ prevent implementations from placing multiple exportable memory -- objects in the same physical or virtual page. Hence, applications -- /should/ avoid creating many small external memory objects whenever -- possible. -- -- Importing memory /must/ not increase overall heap usage within a system. -- However, it /must/ affect the following per-process values: -- -- - 'Vulkan.Core11.Promoted_From_VK_KHR_maintenance3.PhysicalDeviceMaintenance3Properties'::@maxMemoryAllocationCount@ -- -- - 'Vulkan.Extensions.VK_EXT_memory_budget.PhysicalDeviceMemoryBudgetPropertiesEXT'::@heapUsage@ -- -- When performing a memory import operation, it is the responsibility of -- the application to ensure the external handles and their associated -- payloads meet all valid usage requirements. However, implementations -- /must/ perform sufficient validation of external handles and payloads to -- ensure that the operation results in a valid memory object which will -- not cause program termination, device loss, queue stalls, or corruption -- of other resources when used as allowed according to its allocation -- parameters. If the external handle provided does not meet these -- requirements, the implementation /must/ fail the memory import operation -- with the error code -- 'Vulkan.Core10.Enums.Result.ERROR_INVALID_EXTERNAL_HANDLE'. If the -- parameters define an export operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID', -- implementations /should/ not strictly follow @memoryTypeIndex@. Instead, -- they /should/ modify the allocation internally to use the required -- memory type for the application’s given usage. This is because for an -- export operation, there is currently no way for the client to know the -- memory type index before allocating. -- -- == Valid Usage -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-07897# If the parameters -- do not define an -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-import-operation import or export operation>, -- @allocationSize@ /must/ be greater than @0@ -- -- - #VUID-VkMemoryAllocateInfo-None-06657# The parameters /must/ not -- define more than one -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-import-operation import operation> -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-07899# If the parameters -- define an export operation and the handle type is not -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID' -- , @allocationSize@ /must/ be greater than @0@ -- -- - #VUID-VkMemoryAllocateInfo-buffer-06380# If the parameters define an -- import operation from an -- 'Vulkan.Extensions.Handles.BufferCollectionFUCHSIA', and -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@buffer@ -- is present and non-NULL, -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.ImportMemoryBufferCollectionFUCHSIA'::@collection@ -- and -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.ImportMemoryBufferCollectionFUCHSIA'::@index@ -- must match -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionBufferCreateInfoFUCHSIA'::@collection@ -- and -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionBufferCreateInfoFUCHSIA'::@index@, -- respectively, of the -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionBufferCreateInfoFUCHSIA' -- structure used to create the -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@buffer@ -- -- - #VUID-VkMemoryAllocateInfo-image-06381# If the parameters define an -- import operation from an -- 'Vulkan.Extensions.Handles.BufferCollectionFUCHSIA', and -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@image@ -- is present and non-NULL, -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.ImportMemoryBufferCollectionFUCHSIA'::@collection@ -- and -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.ImportMemoryBufferCollectionFUCHSIA'::@index@ -- must match -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionImageCreateInfoFUCHSIA'::@collection@ -- and -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionImageCreateInfoFUCHSIA'::@index@, -- respectively, of the -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionImageCreateInfoFUCHSIA' -- structure used to create the -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@image@ -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-06382# If the parameters -- define an import operation from an -- 'Vulkan.Extensions.Handles.BufferCollectionFUCHSIA', -- @allocationSize@ /must/ match -- 'Vulkan.Core10.MemoryManagement.MemoryRequirements'::@size@ value -- retrieved by -- 'Vulkan.Core10.MemoryManagement.getImageMemoryRequirements' or -- 'Vulkan.Core10.MemoryManagement.getBufferMemoryRequirements' for -- image-based or buffer-based collections respectively -- -- - #VUID-VkMemoryAllocateInfo-pNext-06383# If the parameters define an -- import operation from an -- 'Vulkan.Extensions.Handles.BufferCollectionFUCHSIA', the @pNext@ -- chain /must/ include a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure with either its @image@ or @buffer@ field set to a value -- other than 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-VkMemoryAllocateInfo-image-06384# If the parameters define an -- import operation from an -- 'Vulkan.Extensions.Handles.BufferCollectionFUCHSIA' and -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@image@ -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the @image@ /must/ -- be created with a -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionImageCreateInfoFUCHSIA' -- structure chained to its -- 'Vulkan.Core10.Image.ImageCreateInfo'::@pNext@ pointer -- -- - #VUID-VkMemoryAllocateInfo-buffer-06385# If the parameters define an -- import operation from an -- 'Vulkan.Extensions.Handles.BufferCollectionFUCHSIA' and -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@buffer@ -- is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', the @buffer@ /must/ -- be created with a -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionBufferCreateInfoFUCHSIA' -- structure chained to its -- 'Vulkan.Core10.Buffer.BufferCreateInfo'::@pNext@ pointer -- -- - #VUID-VkMemoryAllocateInfo-memoryTypeIndex-06386# If the parameters -- define an import operation from an -- 'Vulkan.Extensions.Handles.BufferCollectionFUCHSIA', -- @memoryTypeIndex@ /must/ be from -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.BufferCollectionPropertiesFUCHSIA' -- as retrieved by -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.getBufferCollectionPropertiesFUCHSIA' -- -- - #VUID-VkMemoryAllocateInfo-pNext-00639# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExportMemoryAllocateInfo' -- structure, and any of the handle types specified in -- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExportMemoryAllocateInfo'::@handleTypes@ -- require a dedicated allocation, as reported by -- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2' -- in -- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.ExternalImageFormatProperties'::@externalMemoryProperties.externalMemoryFeatures@, -- or by -- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.getPhysicalDeviceExternalBufferProperties' -- in -- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.ExternalBufferProperties'::@externalMemoryProperties.externalMemoryFeatures@, -- the @pNext@ chain /must/ include a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- or -- 'Vulkan.Extensions.VK_NV_dedicated_allocation.DedicatedAllocationMemoryAllocateInfoNV' -- structure with either its @image@ or @buffer@ member set to a value -- other than 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-VkMemoryAllocateInfo-pNext-00640# If the @pNext@ chain -- includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExportMemoryAllocateInfo' -- structure, it /must/ not include a -- 'Vulkan.Extensions.VK_NV_external_memory.ExportMemoryAllocateInfoNV' -- or -- 'Vulkan.Extensions.VK_NV_external_memory_win32.ExportMemoryWin32HandleInfoNV' -- structure -- -- - #VUID-VkMemoryAllocateInfo-pNext-00641# If the @pNext@ chain -- includes a -- 'Vulkan.Extensions.VK_KHR_external_memory_win32.ImportMemoryWin32HandleInfoKHR' -- structure, it /must/ not include a -- 'Vulkan.Extensions.VK_NV_external_memory_win32.ImportMemoryWin32HandleInfoNV' -- structure -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-01742# If the parameters -- define an import operation, the external handle specified was -- created by the Vulkan API, and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_OPAQUE_FD_BIT', -- then the values of @allocationSize@ and @memoryTypeIndex@ /must/ -- match those specified when the payload being imported was created -- -- - #VUID-VkMemoryAllocateInfo-None-00643# If the parameters define an -- import operation and the external handle specified was created by -- the Vulkan API, the device mask specified by -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.MemoryAllocateFlagsInfo' -- /must/ match the mask specified when the payload being imported was -- allocated -- -- - #VUID-VkMemoryAllocateInfo-None-00644# If the parameters define an -- import operation and the external handle specified was created by -- the Vulkan API, the list of physical devices that comprise the -- logical device passed to 'allocateMemory' /must/ match the list of -- physical devices that comprise the logical device on which the -- payload was originally allocated -- -- - #VUID-VkMemoryAllocateInfo-memoryTypeIndex-00645# If the parameters -- define an import operation and the external handle is an NT handle -- or a global share handle created outside of the Vulkan API, the -- value of @memoryTypeIndex@ /must/ be one of those returned by -- 'Vulkan.Extensions.VK_KHR_external_memory_win32.getMemoryWin32HandlePropertiesKHR' -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-01743# If the parameters -- define an import operation, the external handle was created by the -- Vulkan API, and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_OPAQUE_WIN32_BIT' -- or -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_OPAQUE_WIN32_KMT_BIT', -- then the values of @allocationSize@ and @memoryTypeIndex@ /must/ -- match those specified when the payload being imported was created -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-00647# If the parameters -- define an import operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_D3D12_HEAP_BIT', -- @allocationSize@ /must/ match the size specified when creating the -- Direct3D 12 heap from which the payload was extracted -- -- - #VUID-VkMemoryAllocateInfo-memoryTypeIndex-00648# If the parameters -- define an import operation and the external handle is a POSIX file -- descriptor created outside of the Vulkan API, the value of -- @memoryTypeIndex@ /must/ be one of those returned by -- 'Vulkan.Extensions.VK_KHR_external_memory_fd.getMemoryFdPropertiesKHR' -- -- - #VUID-VkMemoryAllocateInfo-memoryTypeIndex-01872# If the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-protectedMemory protectedMemory> -- feature is not enabled, the 'MemoryAllocateInfo'::@memoryTypeIndex@ -- /must/ not indicate a memory type that reports -- 'Vulkan.Core10.Enums.MemoryPropertyFlagBits.MEMORY_PROPERTY_PROTECTED_BIT' -- -- - #VUID-VkMemoryAllocateInfo-memoryTypeIndex-01744# If the parameters -- define an import operation and the external handle is a host -- pointer, the value of @memoryTypeIndex@ /must/ be one of those -- returned by -- 'Vulkan.Extensions.VK_EXT_external_memory_host.getMemoryHostPointerPropertiesEXT' -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-01745# If the parameters -- define an import operation and the external handle is a host -- pointer, @allocationSize@ /must/ be an integer multiple of -- 'Vulkan.Extensions.VK_EXT_external_memory_host.PhysicalDeviceExternalMemoryHostPropertiesEXT'::@minImportedHostPointerAlignment@ -- -- - #VUID-VkMemoryAllocateInfo-pNext-02805# If the parameters define an -- import operation and the external handle is a host pointer, the -- @pNext@ chain /must/ not include a -- 'Vulkan.Extensions.VK_NV_dedicated_allocation.DedicatedAllocationMemoryAllocateInfoNV' -- structure with either its @image@ or @buffer@ field set to a value -- other than 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-VkMemoryAllocateInfo-pNext-02806# If the parameters define an -- import operation and the external handle is a host pointer, the -- @pNext@ chain /must/ not include a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure with either its @image@ or @buffer@ field set to a value -- other than 'Vulkan.Core10.APIConstants.NULL_HANDLE' -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-02383# If the parameters -- define an import operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID', -- @allocationSize@ /must/ be the size returned by -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.getAndroidHardwareBufferPropertiesANDROID' -- for the Android hardware buffer -- -- - #VUID-VkMemoryAllocateInfo-pNext-02384# If the parameters define an -- import operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID', -- and the @pNext@ chain does not include a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure or -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo'::@image@ -- is 'Vulkan.Core10.APIConstants.NULL_HANDLE', the Android hardware -- buffer /must/ have a @AHardwareBuffer_Desc@::@format@ of -- @AHARDWAREBUFFER_FORMAT_BLOB@ and a @AHardwareBuffer_Desc@::@usage@ -- that includes @AHARDWAREBUFFER_USAGE_GPU_DATA_BUFFER@ -- -- - #VUID-VkMemoryAllocateInfo-memoryTypeIndex-02385# If the parameters -- define an import operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID', -- @memoryTypeIndex@ /must/ be one of those returned by -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.getAndroidHardwareBufferPropertiesANDROID' -- for the Android hardware buffer -- -- - #VUID-VkMemoryAllocateInfo-pNext-01874# If the parameters do not -- define an import operation, and the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExportMemoryAllocateInfo' -- structure with -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID' -- included in its @handleTypes@ member, and the @pNext@ chain includes -- a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure with @image@ not equal to -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', then @allocationSize@ -- /must/ be @0@ -- -- - #VUID-VkMemoryAllocateInfo-pNext-07900# If the parameters define an -- export operation, the handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID', -- and the @pNext@ does not include a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure, @allocationSize@ /must/ be greater than @0@ -- -- - #VUID-VkMemoryAllocateInfo-pNext-07901# If the parameters define an -- export operation, the handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ANDROID_HARDWARE_BUFFER_BIT_ANDROID', -- and the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure with @buffer@ set to a valid -- 'Vulkan.Core10.Handles.Buffer' object, @allocationSize@ /must/ be -- greater than @0@ -- -- - #VUID-VkMemoryAllocateInfo-pNext-02386# If the parameters define an -- import operation, the external handle is an Android hardware buffer, -- and the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- with @image@ that is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', -- the Android hardware buffer’s -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AHardwareBuffer'::@usage@ -- /must/ include at least one of -- @AHARDWAREBUFFER_USAGE_GPU_FRAMEBUFFER@, -- @AHARDWAREBUFFER_USAGE_GPU_SAMPLED_IMAGE@ or -- @AHARDWAREBUFFER_USAGE_GPU_DATA_BUFFER@ -- -- - #VUID-VkMemoryAllocateInfo-pNext-02387# If the parameters define an -- import operation, the external handle is an Android hardware buffer, -- and the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- with @image@ that is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', -- the format of @image@ /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' or the format returned -- by -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.getAndroidHardwareBufferPropertiesANDROID' -- in -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AndroidHardwareBufferFormatPropertiesANDROID'::@format@ -- for the Android hardware buffer -- -- - #VUID-VkMemoryAllocateInfo-pNext-02388# If the parameters define an -- import operation, the external handle is an Android hardware buffer, -- and the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure with @image@ that is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', the width, height, and -- array layer dimensions of @image@ and the Android hardware buffer’s -- @AHardwareBuffer_Desc@ /must/ be identical -- -- - #VUID-VkMemoryAllocateInfo-pNext-02389# If the parameters define an -- import operation, the external handle is an Android hardware buffer, -- and the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure with @image@ that is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the Android hardware -- buffer’s -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AHardwareBuffer'::@usage@ -- includes @AHARDWAREBUFFER_USAGE_GPU_MIPMAP_COMPLETE@, the @image@ -- /must/ have a complete mipmap chain -- -- - #VUID-VkMemoryAllocateInfo-pNext-02586# If the parameters define an -- import operation, the external handle is an Android hardware buffer, -- and the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure with @image@ that is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', and the Android hardware -- buffer’s -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.AHardwareBuffer'::@usage@ -- does not include @AHARDWAREBUFFER_USAGE_GPU_MIPMAP_COMPLETE@, the -- @image@ /must/ have exactly one mipmap level -- -- - #VUID-VkMemoryAllocateInfo-pNext-02390# If the parameters define an -- import operation, the external handle is an Android hardware buffer, -- and the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure with @image@ that is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', each bit set in the usage -- of @image@ /must/ be listed in -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-android-hardware-buffer-usage AHardwareBuffer Usage Equivalence>, -- and if there is a corresponding @AHARDWAREBUFFER_USAGE@ bit listed -- that bit /must/ be included in the Android hardware buffer’s -- @AHardwareBuffer_Desc@::@usage@ -- -- - #VUID-VkMemoryAllocateInfo-screenBufferImport-08941# If the -- parameters define an import operation and the external handle type -- is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_SCREEN_BUFFER_BIT_QNX', -- 'Vulkan.Extensions.VK_QNX_external_memory_screen_buffer.PhysicalDeviceExternalMemoryScreenBufferFeaturesQNX'::@screenBufferImport@ -- /must/ be enabled -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-08942# If the parameters -- define an import operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_SCREEN_BUFFER_BIT_QNX', -- @allocationSize@ /must/ be the size returned by -- 'Vulkan.Extensions.VK_QNX_external_memory_screen_buffer.getScreenBufferPropertiesQNX' -- for the QNX Screen buffer -- -- - #VUID-VkMemoryAllocateInfo-memoryTypeIndex-08943# If the parameters -- define an import operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_SCREEN_BUFFER_BIT_QNX', -- @memoryTypeIndex@ /must/ be one of those returned by -- 'Vulkan.Extensions.VK_QNX_external_memory_screen_buffer.getScreenBufferPropertiesQNX' -- for the QNX Screen buffer -- -- - #VUID-VkMemoryAllocateInfo-pNext-08944# If the parameters define an -- import operation, the external handle is a QNX Screen buffer, and -- the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- with @image@ that is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', -- the QNX Screen’s buffer must be a -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-external-screen-buffer-validity valid QNX Screen buffer> -- -- - #VUID-VkMemoryAllocateInfo-pNext-08945# If the parameters define an -- import operation, the external handle is an QNX Screen buffer, and -- the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- with @image@ that is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', -- the format of @image@ /must/ be -- 'Vulkan.Core10.Enums.Format.FORMAT_UNDEFINED' or the format returned -- by -- 'Vulkan.Extensions.VK_QNX_external_memory_screen_buffer.getScreenBufferPropertiesQNX' -- in -- 'Vulkan.Extensions.VK_QNX_external_memory_screen_buffer.ScreenBufferFormatPropertiesQNX'::@format@ -- for the QNX Screen buffer -- -- - #VUID-VkMemoryAllocateInfo-pNext-08946# If the parameters define an -- import operation, the external handle is a QNX Screen buffer, and -- the @pNext@ chain includes a -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo' -- structure with @image@ that is not -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', the width, height, and -- array layer dimensions of @image@ and the QNX Screen buffer’s -- 'Vulkan.Extensions.VK_QNX_external_memory_screen_buffer.Screen_buffer' -- must be identical -- -- - #VUID-VkMemoryAllocateInfo-opaqueCaptureAddress-03329# If -- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.MemoryOpaqueCaptureAddressAllocateInfo'::@opaqueCaptureAddress@ -- is not zero, -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.MemoryAllocateFlagsInfo'::@flags@ -- /must/ include -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT' -- -- - #VUID-VkMemoryAllocateInfo-flags-03330# If -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.MemoryAllocateFlagsInfo'::@flags@ -- includes -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT', -- the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-bufferDeviceAddressCaptureReplay bufferDeviceAddressCaptureReplay> -- feature /must/ be enabled -- -- - #VUID-VkMemoryAllocateInfo-flags-03331# If -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.MemoryAllocateFlagsInfo'::@flags@ -- includes -- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT', -- the -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-bufferDeviceAddress bufferDeviceAddress> -- feature /must/ be enabled -- -- - #VUID-VkMemoryAllocateInfo-pNext-03332# If the @pNext@ chain -- includes a -- 'Vulkan.Extensions.VK_EXT_external_memory_host.ImportMemoryHostPointerInfoEXT' -- structure, -- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.MemoryOpaqueCaptureAddressAllocateInfo'::@opaqueCaptureAddress@ -- /must/ be zero -- -- - #VUID-VkMemoryAllocateInfo-opaqueCaptureAddress-03333# If the -- parameters define an import operation, -- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.MemoryOpaqueCaptureAddressAllocateInfo'::@opaqueCaptureAddress@ -- /must/ be zero -- -- - #VUID-VkMemoryAllocateInfo-None-04749# If the parameters define an -- import operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ZIRCON_VMO_BIT_FUCHSIA', -- the value of @memoryTypeIndex@ /must/ be an index identifying a -- memory type from the @memoryTypeBits@ field of the -- 'Vulkan.Extensions.VK_FUCHSIA_external_memory.MemoryZirconHandlePropertiesFUCHSIA' -- structure populated by a call to -- 'Vulkan.Extensions.VK_FUCHSIA_external_memory.getMemoryZirconHandlePropertiesFUCHSIA' -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-07902# If the parameters -- define an import operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ZIRCON_VMO_BIT_FUCHSIA', -- the value of @allocationSize@ /must/ be greater than @0@ -- -- - #VUID-VkMemoryAllocateInfo-allocationSize-07903# If the parameters -- define an import operation and the external handle type is -- 'Vulkan.Core11.Enums.ExternalMemoryHandleTypeFlagBits.EXTERNAL_MEMORY_HANDLE_TYPE_ZIRCON_VMO_BIT_FUCHSIA', -- the value of @allocationSize@ /must/ be less than or equal to the -- size of the VMO as determined by @zx_vmo_get_size@(@handle@) where -- @handle@ is the VMO handle to the imported external memory -- -- - #VUID-VkMemoryAllocateInfo-pNext-06780# If the @pNext@ chain -- includes a -- 'Vulkan.Extensions.VK_EXT_metal_objects.ExportMetalObjectCreateInfoEXT' -- structure, its @exportObjectType@ member /must/ be -- 'Vulkan.Extensions.VK_EXT_metal_objects.EXPORT_METAL_OBJECT_TYPE_METAL_BUFFER_BIT_EXT' -- -- == Valid Usage (Implicit) -- -- - #VUID-VkMemoryAllocateInfo-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO' -- -- - #VUID-VkMemoryAllocateInfo-pNext-pNext# Each @pNext@ member of any -- structure (including this one) in the @pNext@ chain /must/ be either -- @NULL@ or a pointer to a valid instance of -- 'Vulkan.Extensions.VK_NV_dedicated_allocation.DedicatedAllocationMemoryAllocateInfoNV', -- 'Vulkan.Core11.Promoted_From_VK_KHR_external_memory.ExportMemoryAllocateInfo', -- 'Vulkan.Extensions.VK_NV_external_memory.ExportMemoryAllocateInfoNV', -- 'Vulkan.Extensions.VK_KHR_external_memory_win32.ExportMemoryWin32HandleInfoKHR', -- 'Vulkan.Extensions.VK_NV_external_memory_win32.ExportMemoryWin32HandleInfoNV', -- 'Vulkan.Extensions.VK_EXT_metal_objects.ExportMetalObjectCreateInfoEXT', -- 'Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer.ImportAndroidHardwareBufferInfoANDROID', -- 'Vulkan.Extensions.VK_FUCHSIA_buffer_collection.ImportMemoryBufferCollectionFUCHSIA', -- 'Vulkan.Extensions.VK_KHR_external_memory_fd.ImportMemoryFdInfoKHR', -- 'Vulkan.Extensions.VK_EXT_external_memory_host.ImportMemoryHostPointerInfoEXT', -- 'Vulkan.Extensions.VK_KHR_external_memory_win32.ImportMemoryWin32HandleInfoKHR', -- 'Vulkan.Extensions.VK_NV_external_memory_win32.ImportMemoryWin32HandleInfoNV', -- 'Vulkan.Extensions.VK_FUCHSIA_external_memory.ImportMemoryZirconHandleInfoFUCHSIA', -- 'Vulkan.Extensions.VK_EXT_metal_objects.ImportMetalBufferInfoEXT', -- 'Vulkan.Extensions.VK_QNX_external_memory_screen_buffer.ImportScreenBufferInfoQNX', -- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.MemoryAllocateFlagsInfo', -- 'Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation.MemoryDedicatedAllocateInfo', -- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.MemoryOpaqueCaptureAddressAllocateInfo', -- or -- 'Vulkan.Extensions.VK_EXT_memory_priority.MemoryPriorityAllocateInfoEXT' -- -- - #VUID-VkMemoryAllocateInfo-sType-unique# The @sType@ value of each -- struct in the @pNext@ chain /must/ be unique, with the exception of -- structures of type -- 'Vulkan.Extensions.VK_EXT_metal_objects.ExportMetalObjectCreateInfoEXT' -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.FundamentalTypes.DeviceSize', -- 'Vulkan.Core10.Enums.StructureType.StructureType', 'allocateMemory' data MemoryAllocateInfo (es :: [Type]) = MemoryAllocateInfo { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure. forall (es :: [*]). MemoryAllocateInfo es -> Chain es next :: Chain es , -- | @allocationSize@ is the size of the allocation in bytes. forall (es :: [*]). MemoryAllocateInfo es -> "offset" ::: DeviceSize allocationSize :: DeviceSize , -- | @memoryTypeIndex@ is an index identifying a memory type from the -- @memoryTypes@ array of the -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceMemoryProperties' -- structure. forall (es :: [*]). MemoryAllocateInfo es -> "memoryRangeCount" ::: Word32 memoryTypeIndex :: Word32 } deriving (Typeable) #if defined(GENERIC_INSTANCES) deriving instance Generic (MemoryAllocateInfo (es :: [Type])) #endif deriving instance Show (Chain es) => Show (MemoryAllocateInfo es) instance Extensible MemoryAllocateInfo where extensibleTypeName :: String extensibleTypeName = String "MemoryAllocateInfo" setNext :: forall (ds :: [*]) (es :: [*]). MemoryAllocateInfo ds -> Chain es -> MemoryAllocateInfo es setNext MemoryAllocateInfo{"memoryRangeCount" ::: Word32 "offset" ::: DeviceSize Chain ds memoryTypeIndex :: "memoryRangeCount" ::: Word32 allocationSize :: "offset" ::: DeviceSize next :: Chain ds $sel:memoryTypeIndex:MemoryAllocateInfo :: forall (es :: [*]). MemoryAllocateInfo es -> "memoryRangeCount" ::: Word32 $sel:allocationSize:MemoryAllocateInfo :: forall (es :: [*]). MemoryAllocateInfo es -> "offset" ::: DeviceSize $sel:next:MemoryAllocateInfo :: forall (es :: [*]). MemoryAllocateInfo es -> Chain es ..} Chain es next' = MemoryAllocateInfo{$sel:next:MemoryAllocateInfo :: Chain es next = Chain es next', "memoryRangeCount" ::: Word32 "offset" ::: DeviceSize memoryTypeIndex :: "memoryRangeCount" ::: Word32 allocationSize :: "offset" ::: DeviceSize $sel:memoryTypeIndex:MemoryAllocateInfo :: "memoryRangeCount" ::: Word32 $sel:allocationSize:MemoryAllocateInfo :: "offset" ::: DeviceSize ..} getNext :: forall (es :: [*]). MemoryAllocateInfo es -> Chain es getNext MemoryAllocateInfo{"memoryRangeCount" ::: Word32 "offset" ::: DeviceSize Chain es memoryTypeIndex :: "memoryRangeCount" ::: Word32 allocationSize :: "offset" ::: DeviceSize next :: Chain es $sel:memoryTypeIndex:MemoryAllocateInfo :: forall (es :: [*]). MemoryAllocateInfo es -> "memoryRangeCount" ::: Word32 $sel:allocationSize:MemoryAllocateInfo :: forall (es :: [*]). MemoryAllocateInfo es -> "offset" ::: DeviceSize $sel:next:MemoryAllocateInfo :: forall (es :: [*]). MemoryAllocateInfo es -> Chain es ..} = Chain es next extends :: forall e b proxy. Typeable e => proxy e -> (Extends MemoryAllocateInfo e => b) -> Maybe b extends :: forall e b (proxy :: * -> *). Typeable e => proxy e -> (Extends MemoryAllocateInfo e => b) -> Maybe b extends proxy e _ Extends MemoryAllocateInfo e => b f | Just e :~: ImportScreenBufferInfoQNX Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImportScreenBufferInfoQNX = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ImportMetalBufferInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImportMetalBufferInfoEXT = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ExportMetalObjectCreateInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ExportMetalObjectCreateInfoEXT = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ImportMemoryBufferCollectionFUCHSIA Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImportMemoryBufferCollectionFUCHSIA = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: MemoryOpaqueCaptureAddressAllocateInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @MemoryOpaqueCaptureAddressAllocateInfo = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: MemoryPriorityAllocateInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @MemoryPriorityAllocateInfoEXT = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ImportAndroidHardwareBufferInfoANDROID Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImportAndroidHardwareBufferInfoANDROID = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ImportMemoryHostPointerInfoEXT Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImportMemoryHostPointerInfoEXT = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: MemoryDedicatedAllocateInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @MemoryDedicatedAllocateInfo = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: MemoryAllocateFlagsInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @MemoryAllocateFlagsInfo = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ImportMemoryFdInfoKHR Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImportMemoryFdInfoKHR = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ImportMemoryZirconHandleInfoFUCHSIA Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImportMemoryZirconHandleInfoFUCHSIA = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ExportMemoryWin32HandleInfoKHR Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ExportMemoryWin32HandleInfoKHR = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ImportMemoryWin32HandleInfoKHR Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImportMemoryWin32HandleInfoKHR = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ExportMemoryAllocateInfo Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ExportMemoryAllocateInfo = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ExportMemoryWin32HandleInfoNV Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ExportMemoryWin32HandleInfoNV = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ImportMemoryWin32HandleInfoNV Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ImportMemoryWin32HandleInfoNV = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: ExportMemoryAllocateInfoNV Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @ExportMemoryAllocateInfoNV = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Just e :~: DedicatedAllocationMemoryAllocateInfoNV Refl <- forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => Maybe (a :~: b) eqT @e @DedicatedAllocationMemoryAllocateInfoNV = forall a. a -> Maybe a Just Extends MemoryAllocateInfo e => b f | Bool otherwise = forall a. Maybe a Nothing instance ( Extendss MemoryAllocateInfo es , PokeChain es ) => ToCStruct (MemoryAllocateInfo es) where withCStruct :: forall b. MemoryAllocateInfo es -> (Ptr (MemoryAllocateInfo es) -> IO b) -> IO b withCStruct MemoryAllocateInfo es x Ptr (MemoryAllocateInfo es) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 32 forall a b. (a -> b) -> a -> b $ \Ptr (MemoryAllocateInfo es) p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct Ptr (MemoryAllocateInfo es) p MemoryAllocateInfo es x (Ptr (MemoryAllocateInfo es) -> IO b f Ptr (MemoryAllocateInfo es) p) pokeCStruct :: forall b. Ptr (MemoryAllocateInfo es) -> MemoryAllocateInfo es -> IO b -> IO b pokeCStruct Ptr (MemoryAllocateInfo es) p MemoryAllocateInfo{"memoryRangeCount" ::: Word32 "offset" ::: DeviceSize Chain es memoryTypeIndex :: "memoryRangeCount" ::: Word32 allocationSize :: "offset" ::: DeviceSize next :: Chain es $sel:memoryTypeIndex:MemoryAllocateInfo :: forall (es :: [*]). MemoryAllocateInfo es -> "memoryRangeCount" ::: Word32 $sel:allocationSize:MemoryAllocateInfo :: forall (es :: [*]). MemoryAllocateInfo es -> "offset" ::: DeviceSize $sel:next:MemoryAllocateInfo :: forall (es :: [*]). MemoryAllocateInfo es -> Chain es ..} 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 (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO) "data" ::: Ptr () pNext'' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . 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 (es :: [*]) a. PokeChain es => Chain es -> (Ptr (Chain es) -> IO a) -> IO a withChain (Chain es next) 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 (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) "data" ::: Ptr () pNext'' 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 (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr DeviceSize)) ("offset" ::: DeviceSize allocationSize) 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 (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Word32)) ("memoryRangeCount" ::: Word32 memoryTypeIndex) 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 (MemoryAllocateInfo es) -> IO b -> IO b pokeZeroCStruct Ptr (MemoryAllocateInfo es) p 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 (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO) "data" ::: Ptr () pNext' <- forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap forall a b. Ptr a -> Ptr b castPtr forall b c a. (b -> c) -> (a -> b) -> a -> c . 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 (es :: [*]) a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a withZeroChain @es 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 (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) "data" ::: Ptr () pNext' 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 (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr DeviceSize)) (forall a. Zero a => a zero) 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 (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Word32)) (forall a. Zero a => a zero) forall (t :: (* -> *) -> * -> *) (m :: * -> *) a. (MonadTrans t, Monad m) => m a -> t m a lift forall a b. (a -> b) -> a -> b $ IO b f instance ( Extendss MemoryAllocateInfo es , PeekChain es ) => FromCStruct (MemoryAllocateInfo es) where peekCStruct :: Ptr (MemoryAllocateInfo es) -> IO (MemoryAllocateInfo es) peekCStruct Ptr (MemoryAllocateInfo es) p = do "data" ::: Ptr () pNext <- forall a. Storable a => Ptr a -> IO a peek @(Ptr ()) ((Ptr (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 8 :: Ptr (Ptr ()))) Chain es next <- forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es) peekChain (forall a b. Ptr a -> Ptr b castPtr "data" ::: Ptr () pNext) "offset" ::: DeviceSize allocationSize <- forall a. Storable a => Ptr a -> IO a peek @DeviceSize ((Ptr (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr DeviceSize)) "memoryRangeCount" ::: Word32 memoryTypeIndex <- forall a. Storable a => Ptr a -> IO a peek @Word32 ((Ptr (MemoryAllocateInfo es) p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr Word32)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ forall (es :: [*]). Chain es -> ("offset" ::: DeviceSize) -> ("memoryRangeCount" ::: Word32) -> MemoryAllocateInfo es MemoryAllocateInfo Chain es next "offset" ::: DeviceSize allocationSize "memoryRangeCount" ::: Word32 memoryTypeIndex instance es ~ '[] => Zero (MemoryAllocateInfo es) where zero :: MemoryAllocateInfo es zero = forall (es :: [*]). Chain es -> ("offset" ::: DeviceSize) -> ("memoryRangeCount" ::: Word32) -> MemoryAllocateInfo es MemoryAllocateInfo () forall a. Zero a => a zero forall a. Zero a => a zero -- | VkMappedMemoryRange - Structure specifying a mapped memory range -- -- == Valid Usage -- -- - #VUID-VkMappedMemoryRange-memory-00684# @memory@ /must/ be currently -- host mapped -- -- - #VUID-VkMappedMemoryRange-size-00685# If @size@ is not equal to -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE', @offset@ and @size@ /must/ -- specify a range contained within the currently mapped range of -- @memory@ -- -- - #VUID-VkMappedMemoryRange-size-00686# If @size@ is equal to -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE', @offset@ /must/ be within -- the currently mapped range of @memory@ -- -- - #VUID-VkMappedMemoryRange-offset-00687# @offset@ /must/ be a -- multiple of -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@nonCoherentAtomSize@ -- -- - #VUID-VkMappedMemoryRange-size-01389# If @size@ is equal to -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE', the end of the current -- mapping of @memory@ /must/ either be a multiple of -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@nonCoherentAtomSize@ -- bytes from the beginning of the memory object, or be equal to the -- end of the memory object -- -- - #VUID-VkMappedMemoryRange-size-01390# If @size@ is not equal to -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE', @size@ /must/ either be a -- multiple of -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@nonCoherentAtomSize@, -- or @offset@ plus @size@ /must/ equal the size of @memory@ -- -- == Valid Usage (Implicit) -- -- - #VUID-VkMappedMemoryRange-sType-sType# @sType@ /must/ be -- 'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MAPPED_MEMORY_RANGE' -- -- - #VUID-VkMappedMemoryRange-pNext-pNext# @pNext@ /must/ be @NULL@ -- -- - #VUID-VkMappedMemoryRange-memory-parameter# @memory@ /must/ be a -- valid 'Vulkan.Core10.Handles.DeviceMemory' handle -- -- = See Also -- -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>, -- 'Vulkan.Core10.Handles.DeviceMemory', -- 'Vulkan.Core10.FundamentalTypes.DeviceSize', -- 'Vulkan.Core10.Enums.StructureType.StructureType', -- 'flushMappedMemoryRanges', 'invalidateMappedMemoryRanges' data MappedMemoryRange = MappedMemoryRange { -- | @memory@ is the memory object to which this range belongs. MappedMemoryRange -> DeviceMemory memory :: DeviceMemory , -- | @offset@ is the zero-based byte offset from the beginning of the memory -- object. MappedMemoryRange -> "offset" ::: DeviceSize offset :: DeviceSize , -- | @size@ is either the size of range, or -- 'Vulkan.Core10.APIConstants.WHOLE_SIZE' to affect the range from -- @offset@ to the end of the current mapping of the allocation. MappedMemoryRange -> "offset" ::: DeviceSize size :: DeviceSize } deriving (Typeable, MappedMemoryRange -> MappedMemoryRange -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: MappedMemoryRange -> MappedMemoryRange -> Bool $c/= :: MappedMemoryRange -> MappedMemoryRange -> Bool == :: MappedMemoryRange -> MappedMemoryRange -> Bool $c== :: MappedMemoryRange -> MappedMemoryRange -> Bool Eq) #if defined(GENERIC_INSTANCES) deriving instance Generic (MappedMemoryRange) #endif deriving instance Show MappedMemoryRange instance ToCStruct MappedMemoryRange where withCStruct :: forall b. MappedMemoryRange -> (("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b) -> IO b withCStruct MappedMemoryRange x ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b f = forall a b. Int -> (Ptr a -> IO b) -> IO b allocaBytes Int 40 forall a b. (a -> b) -> a -> b $ \"pMemoryRanges" ::: Ptr MappedMemoryRange p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pMemoryRanges" ::: Ptr MappedMemoryRange p MappedMemoryRange x (("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b f "pMemoryRanges" ::: Ptr MappedMemoryRange p) pokeCStruct :: forall b. ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> MappedMemoryRange -> IO b -> IO b pokeCStruct "pMemoryRanges" ::: Ptr MappedMemoryRange p MappedMemoryRange{"offset" ::: DeviceSize DeviceMemory size :: "offset" ::: DeviceSize offset :: "offset" ::: DeviceSize memory :: DeviceMemory $sel:size:MappedMemoryRange :: MappedMemoryRange -> "offset" ::: DeviceSize $sel:offset:MappedMemoryRange :: MappedMemoryRange -> "offset" ::: DeviceSize $sel:memory:MappedMemoryRange :: MappedMemoryRange -> DeviceMemory ..} IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_MAPPED_MEMORY_RANGE) forall a. Storable a => Ptr a -> a -> IO () poke (("pMemoryRanges" ::: Ptr MappedMemoryRange 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 (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr DeviceMemory)) (DeviceMemory memory) forall a. Storable a => Ptr a -> a -> IO () poke (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr DeviceSize)) ("offset" ::: DeviceSize offset) forall a. Storable a => Ptr a -> a -> IO () poke (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr DeviceSize)) ("offset" ::: DeviceSize size) IO b f cStructSize :: Int cStructSize = Int 40 cStructAlignment :: Int cStructAlignment = Int 8 pokeZeroCStruct :: forall b. ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b -> IO b pokeZeroCStruct "pMemoryRanges" ::: Ptr MappedMemoryRange p IO b f = do forall a. Storable a => Ptr a -> a -> IO () poke (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 0 :: Ptr StructureType)) (StructureType STRUCTURE_TYPE_MAPPED_MEMORY_RANGE) forall a. Storable a => Ptr a -> a -> IO () poke (("pMemoryRanges" ::: Ptr MappedMemoryRange 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 (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr DeviceMemory)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr DeviceSize)) (forall a. Zero a => a zero) forall a. Storable a => Ptr a -> a -> IO () poke (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr DeviceSize)) (forall a. Zero a => a zero) IO b f instance FromCStruct MappedMemoryRange where peekCStruct :: ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO MappedMemoryRange peekCStruct "pMemoryRanges" ::: Ptr MappedMemoryRange p = do DeviceMemory memory <- forall a. Storable a => Ptr a -> IO a peek @DeviceMemory (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 16 :: Ptr DeviceMemory)) "offset" ::: DeviceSize offset <- forall a. Storable a => Ptr a -> IO a peek @DeviceSize (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 24 :: Ptr DeviceSize)) "offset" ::: DeviceSize size <- forall a. Storable a => Ptr a -> IO a peek @DeviceSize (("pMemoryRanges" ::: Ptr MappedMemoryRange p forall a b. Ptr a -> Int -> Ptr b `plusPtr` Int 32 :: Ptr DeviceSize)) forall (f :: * -> *) a. Applicative f => a -> f a pure forall a b. (a -> b) -> a -> b $ DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MappedMemoryRange MappedMemoryRange DeviceMemory memory "offset" ::: DeviceSize offset "offset" ::: DeviceSize size instance Storable MappedMemoryRange where sizeOf :: MappedMemoryRange -> Int sizeOf ~MappedMemoryRange _ = Int 40 alignment :: MappedMemoryRange -> Int alignment ~MappedMemoryRange _ = Int 8 peek :: ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO MappedMemoryRange peek = forall a. FromCStruct a => Ptr a -> IO a peekCStruct poke :: ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> MappedMemoryRange -> IO () poke "pMemoryRanges" ::: Ptr MappedMemoryRange ptr MappedMemoryRange poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b pokeCStruct "pMemoryRanges" ::: Ptr MappedMemoryRange ptr MappedMemoryRange poked (forall (f :: * -> *) a. Applicative f => a -> f a pure ()) instance Zero MappedMemoryRange where zero :: MappedMemoryRange zero = DeviceMemory -> ("offset" ::: DeviceSize) -> ("offset" ::: DeviceSize) -> MappedMemoryRange MappedMemoryRange forall a. Zero a => a zero forall a. Zero a => a zero forall a. Zero a => a zero