vulkan-3.3.1: Bindings to the Vulkan graphics API.
Safe HaskellNone
LanguageHaskell2010

Vulkan.Core10.Memory

Synopsis

Documentation

allocateMemory Source #

Arguments

:: forall a io. (Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) 
=> Device

device is the logical device that owns the memory.

-> MemoryAllocateInfo a

pAllocateInfo is a pointer to a MemoryAllocateInfo structure describing parameters of the allocation. A successful returned allocation must use the requested parameters — no substitution is permitted by the implementation.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> io DeviceMemory 

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 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 Device may be restricted by implementation- or platform-dependent limits. If a call to allocateMemory would cause the total number of allocations to exceed these limits, such a call will fail and must return ERROR_TOO_MANY_OBJECTS. The maxMemoryAllocationCount feature describes the number of allocations that can exist simultaneously before encountering these internal limits.

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 ERROR_OUT_OF_DEVICE_MEMORY must be returned. This limit is advertised in 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.

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, DeviceMemory, MemoryAllocateInfo

withMemory :: forall a io r. (Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) => Device -> MemoryAllocateInfo a -> Maybe AllocationCallbacks -> (io DeviceMemory -> (DeviceMemory -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to allocateMemory and freeMemory

To ensure that freeMemory is always called: pass bracket (or the allocate function from your favourite resource management library) as the first argument. To just extract the pair pass (,) as the first argument.

freeMemory Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the memory.

-> DeviceMemory

memory is the DeviceMemory object to be freed.

-> ("allocator" ::: Maybe AllocationCallbacks)

pAllocator controls host memory allocation as described in the Memory Allocation chapter.

-> 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. If there are still any bound images or buffers, the memory may not be immediately released by the implementation, but must be released by the time all bound images and buffers have been destroyed. Once memory is 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 Resource Memory Association section.

If a memory object is mapped at the time it is freed, it is implicitly unmapped.

Note

As described 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

  • All submitted commands that refer to memory (via images or buffers) must have completed execution

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If memory is not NULL_HANDLE, memory must be a valid DeviceMemory handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • 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

AllocationCallbacks, Device, DeviceMemory

mapMemory Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the memory.

-> DeviceMemory

memory is the DeviceMemory object to be mapped.

-> ("offset" ::: DeviceSize)

offset is a zero-based byte offset from the beginning of the memory object.

-> DeviceSize

size is the size of the memory range to map, or WHOLE_SIZE to map from offset to the end of the allocation.

-> MemoryMapFlags

flags is reserved for future use.

-> io ("data" ::: Ptr ()) 

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 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 here for details on fulfilling such a guarantee). If the device memory was allocated without the 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 PhysicalDeviceLimits::nonCoherentAtomSize, and round the end of the range up to the nearest multiple of 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 Synchronization and Cache Control as they are crucial to maintaining memory access ordering.

Valid Usage

  • memory must not be currently host mapped
  • offset must be less than the size of memory
  • If size is not equal to WHOLE_SIZE, size must be greater than 0
  • If size is not equal to WHOLE_SIZE, size must be less than or equal to the size of the memory minus offset
  • memory must have been created with a memory type that reports MEMORY_PROPERTY_HOST_VISIBLE_BIT
  • memory must not have been allocated with multiple instances

Valid Usage (Implicit)

  • device must be a valid Device handle
  • memory must be a valid DeviceMemory handle
  • flags must be 0
  • ppData must be a valid pointer to a pointer value
  • memory must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to memory must be externally synchronized

Return Codes

Success
Failure

See Also

Device, DeviceMemory, DeviceSize, MemoryMapFlags

withMappedMemory :: forall io r. MonadIO io => Device -> DeviceMemory -> DeviceSize -> DeviceSize -> MemoryMapFlags -> (io (Ptr ()) -> (Ptr () -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to mapMemory and unmapMemory

To ensure that unmapMemory is always called: pass bracket (or the allocate function from your favourite resource management library) as the first argument. To just extract the pair pass (,) as the first argument.

unmapMemory Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the memory.

-> DeviceMemory

memory is the memory object to be unmapped.

-> io () 

vkUnmapMemory - Unmap a previously mapped memory object

Valid Usage

  • memory must be currently host mapped

Valid Usage (Implicit)

  • device must be a valid Device handle
  • memory must be a valid DeviceMemory handle
  • memory must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to memory must be externally synchronized

See Also

Device, DeviceMemory

flushMappedMemoryRanges Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the memory ranges.

device must be a valid Device handle

-> ("memoryRanges" ::: Vector MappedMemoryRange)

pMemoryRanges is a pointer to an array of MappedMemoryRange structures describing the memory ranges to flush.

pMemoryRanges must be a valid pointer to an array of memoryRangeCount valid MappedMemoryRange structures

-> io () 

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 memory domain operations using the ACCESS_HOST_WRITE_BIT 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

Success
Failure

See Also

Device, MappedMemoryRange

invalidateMappedMemoryRanges Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the memory ranges.

device must be a valid Device handle

-> ("memoryRanges" ::: Vector MappedMemoryRange)

pMemoryRanges is a pointer to an array of MappedMemoryRange structures describing the memory ranges to invalidate.

pMemoryRanges must be a valid pointer to an array of memoryRangeCount valid MappedMemoryRange structures

-> io () 

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 ACCESS_HOST_WRITE_BIT and ACCESS_HOST_READ_BIT 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

Success
Failure

See Also

Device, MappedMemoryRange

getDeviceMemoryCommitment Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the memory.

device must be a valid Device handle

-> DeviceMemory

memory is the memory object being queried.

memory must have been created with a memory type that reports MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT

memory must be a valid DeviceMemory handle

memory must have been created, allocated, or retrieved from device

-> io ("committedMemoryInBytes" ::: DeviceSize) 

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

Device, DeviceMemory, DeviceSize

data MemoryAllocateInfo (es :: [Type]) Source #

VkMemoryAllocateInfo - Structure containing parameters of a memory allocation

Description

A MemoryAllocateInfo structure defines a memory import operation if its pNext chain includes one of the following structures:

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.

When performing a memory import operation, it is the responsibility of the application to ensure the external handles meet all valid usage requirements. However, implementations must perform sufficient validation of external handles 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 ERROR_INVALID_EXTERNAL_HANDLE.

Valid Usage

Valid Usage (Implicit)

See Also

DeviceSize, StructureType, allocateMemory

Constructors

MemoryAllocateInfo 

Fields

Instances

Instances details
Extensible MemoryAllocateInfo Source # 
Instance details

Defined in Vulkan.Core10.Memory

Methods

extensibleType :: StructureType Source #

getNext :: forall (es :: [Type]). MemoryAllocateInfo es -> Chain es Source #

setNext :: forall (ds :: [Type]) (es :: [Type]). MemoryAllocateInfo ds -> Chain es -> MemoryAllocateInfo es Source #

extends :: forall e b proxy. Typeable e => proxy e -> (Extends MemoryAllocateInfo e => b) -> Maybe b Source #

Show (Chain es) => Show (MemoryAllocateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Memory

Generic (MemoryAllocateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Memory

Associated Types

type Rep (MemoryAllocateInfo es) :: Type -> Type #

(Extendss MemoryAllocateInfo es, PeekChain es) => FromCStruct (MemoryAllocateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Memory

(Extendss MemoryAllocateInfo es, PokeChain es) => ToCStruct (MemoryAllocateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Memory

es ~ ('[] :: [Type]) => Zero (MemoryAllocateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Memory

type Rep (MemoryAllocateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Memory

type Rep (MemoryAllocateInfo es) = D1 ('MetaData "MemoryAllocateInfo" "Vulkan.Core10.Memory" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "MemoryAllocateInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: (S1 ('MetaSel ('Just "allocationSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DeviceSize) :*: S1 ('MetaSel ('Just "memoryTypeIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32))))

data MappedMemoryRange Source #

VkMappedMemoryRange - Structure specifying a mapped memory range

Valid Usage

  • memory must be currently host mapped
  • If size is not equal to WHOLE_SIZE, offset and size must specify a range contained within the currently mapped range of memory
  • If size is equal to WHOLE_SIZE, offset must be within the currently mapped range of memory
  • If size is equal to WHOLE_SIZE, the end of the current mapping of memory must be a multiple of PhysicalDeviceLimits::nonCoherentAtomSize bytes from the beginning of the memory object
  • offset must be a multiple of PhysicalDeviceLimits::nonCoherentAtomSize
  • If size is not equal to WHOLE_SIZE, size must either be a multiple of PhysicalDeviceLimits::nonCoherentAtomSize, or offset plus size must equal the size of memory

Valid Usage (Implicit)

  • pNext must be NULL
  • memory must be a valid DeviceMemory handle

See Also

DeviceMemory, DeviceSize, StructureType, flushMappedMemoryRanges, invalidateMappedMemoryRanges

Constructors

MappedMemoryRange 

Fields

  • memory :: DeviceMemory

    memory is the memory object to which this range belongs.

  • offset :: DeviceSize

    offset is the zero-based byte offset from the beginning of the memory object.

  • size :: DeviceSize

    size is either the size of range, or WHOLE_SIZE to affect the range from offset to the end of the current mapping of the allocation.

Instances

Instances details
Eq MappedMemoryRange Source # 
Instance details

Defined in Vulkan.Core10.Memory

Show MappedMemoryRange Source # 
Instance details

Defined in Vulkan.Core10.Memory

Generic MappedMemoryRange Source # 
Instance details

Defined in Vulkan.Core10.Memory

Associated Types

type Rep MappedMemoryRange :: Type -> Type #

Storable MappedMemoryRange Source # 
Instance details

Defined in Vulkan.Core10.Memory

FromCStruct MappedMemoryRange Source # 
Instance details

Defined in Vulkan.Core10.Memory

ToCStruct MappedMemoryRange Source # 
Instance details

Defined in Vulkan.Core10.Memory

Zero MappedMemoryRange Source # 
Instance details

Defined in Vulkan.Core10.Memory

type Rep MappedMemoryRange Source # 
Instance details

Defined in Vulkan.Core10.Memory

type Rep MappedMemoryRange = D1 ('MetaData "MappedMemoryRange" "Vulkan.Core10.Memory" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "MappedMemoryRange" 'PrefixI 'True) (S1 ('MetaSel ('Just "memory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DeviceMemory) :*: (S1 ('MetaSel ('Just "offset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DeviceSize) :*: S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DeviceSize))))