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

Vulkan.Core10.Buffer

Synopsis

Documentation

createBuffer Source #

Arguments

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

device is the logical device that creates the buffer object.

-> BufferCreateInfo a

pCreateInfo is a pointer to a BufferCreateInfo structure containing parameters affecting creation of the buffer.

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

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

-> io Buffer 

vkCreateBuffer - Create a new buffer object

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pCreateInfo must be a valid pointer to a valid BufferCreateInfo structure
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • pBuffer must be a valid pointer to a Buffer handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Buffer, BufferCreateInfo, Device

withBuffer :: forall a io r. (Extendss BufferCreateInfo a, PokeChain a, MonadIO io) => Device -> BufferCreateInfo a -> Maybe AllocationCallbacks -> (io Buffer -> (Buffer -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createBuffer and destroyBuffer

To ensure that destroyBuffer 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.

destroyBuffer Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the buffer.

-> Buffer

buffer is the buffer to destroy.

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

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

-> io () 

vkDestroyBuffer - Destroy a buffer object

Valid Usage

  • All submitted commands that refer to buffer, either directly or via a BufferView, must have completed execution
  • If AllocationCallbacks were provided when buffer was created, a compatible set of callbacks must be provided here
  • If no AllocationCallbacks were provided when buffer was created, pAllocator must be NULL

Valid Usage (Implicit)

  • device must be a valid Device handle
  • If buffer is not NULL_HANDLE, buffer must be a valid Buffer handle
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • If buffer is a valid handle, it must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to buffer must be externally synchronized

See Also

AllocationCallbacks, Buffer, Device

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

VkBufferCreateInfo - Structure specifying the parameters of a newly created buffer object

Valid Usage

  • size must be greater than 0

Valid Usage (Implicit)

See Also

BufferCreateFlags, BufferUsageFlags, DeviceSize, SharingMode, StructureType, createBuffer

Constructors

BufferCreateInfo 

Fields

Instances

Instances details
Extensible BufferCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Buffer

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.Buffer

Generic (BufferCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Buffer

Associated Types

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

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

Defined in Vulkan.Core10.Buffer

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

Defined in Vulkan.Core10.Buffer

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

Defined in Vulkan.Core10.Buffer

type Rep (BufferCreateInfo es) Source # 
Instance details

Defined in Vulkan.Core10.Buffer