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

Vulkan.Core10.CommandBuffer

Synopsis

Documentation

allocateCommandBuffers Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the command pool.

-> CommandBufferAllocateInfo

pAllocateInfo is a pointer to a CommandBufferAllocateInfo structure describing parameters of the allocation.

-> io ("commandBuffers" ::: Vector CommandBuffer) 

vkAllocateCommandBuffers - Allocate command buffers from an existing command pool

Description

allocateCommandBuffers can be used to create multiple command buffers. If the creation of any of those command buffers fails, the implementation must destroy all successfully created command buffer objects from this command, set all entries of the pCommandBuffers array to NULL and return the error.

When command buffers are first allocated, they are in the initial state.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pAllocateInfo must be a valid pointer to a valid CommandBufferAllocateInfo structure
  • pCommandBuffers must be a valid pointer to an array of pAllocateInfo->commandBufferCount CommandBuffer handles
  • The value referenced by pAllocateInfo->commandBufferCount must be greater than 0

Host Synchronization

  • Host access to pAllocateInfo->commandPool must be externally synchronized

Return Codes

Success
Failure

See Also

CommandBuffer, CommandBufferAllocateInfo, Device

withCommandBuffers :: forall io r. MonadIO io => Device -> CommandBufferAllocateInfo -> (io (Vector CommandBuffer) -> (Vector CommandBuffer -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to allocateCommandBuffers and freeCommandBuffers

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

freeCommandBuffers Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the command pool.

-> CommandPool

commandPool is the command pool from which the command buffers were allocated.

-> ("commandBuffers" ::: Vector CommandBuffer)

pCommandBuffers is a pointer to an array of handles of command buffers to free.

-> io () 

vkFreeCommandBuffers - Free command buffers

Description

Any primary command buffer that is in the recording or executable state and has any element of pCommandBuffers recorded into it, becomes invalid.

Valid Usage

  • pCommandBuffers must be a valid pointer to an array of commandBufferCount CommandBuffer handles, each element of which must either be a valid handle or NULL

Valid Usage (Implicit)

  • device must be a valid Device handle
  • commandPool must be a valid CommandPool handle
  • commandBufferCount must be greater than 0
  • commandPool must have been created, allocated, or retrieved from device
  • Each element of pCommandBuffers that is a valid handle must have been created, allocated, or retrieved from commandPool

Host Synchronization

  • Host access to commandPool must be externally synchronized
  • Host access to each member of pCommandBuffers must be externally synchronized

See Also

CommandBuffer, CommandPool, Device

beginCommandBuffer Source #

Arguments

:: forall a io. (Extendss CommandBufferBeginInfo a, PokeChain a, MonadIO io) 
=> CommandBuffer

commandBuffer is the handle of the command buffer which is to be put in the recording state.

-> CommandBufferBeginInfo a

pBeginInfo points to a CommandBufferBeginInfo structure defining additional information about how the command buffer begins recording.

-> io () 

vkBeginCommandBuffer - Start recording a command buffer

Valid Usage

Valid Usage (Implicit)

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Return Codes

Success
Failure

See Also

CommandBuffer, CommandBufferBeginInfo

useCommandBuffer :: forall a io r. (Extendss CommandBufferBeginInfo a, PokeChain a, MonadIO io) => CommandBuffer -> CommandBufferBeginInfo a -> io r -> io r Source #

This function will call the supplied action between calls to beginCommandBuffer and endCommandBuffer

Note that endCommandBuffer is *not* called if an exception is thrown by the inner action.

endCommandBuffer Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer to complete recording.

-> io () 

vkEndCommandBuffer - Finish recording a command buffer

Description

If there was an error during recording, the application will be notified by an unsuccessful return code returned by endCommandBuffer. If the application wishes to further use the command buffer, the command buffer must be reset. The command buffer must have been in the recording state, and is moved to the executable state.

Valid Usage

  • If commandBuffer is a primary command buffer, there must not be an active render pass instance
  • All queries made active during the recording of commandBuffer must have been made inactive
  • Conditional rendering must not be active
  • If commandBuffer is a secondary command buffer, there must not be an outstanding cmdBeginDebugUtilsLabelEXT command recorded to commandBuffer that has not previously been ended by a call to cmdEndDebugUtilsLabelEXT
  • If commandBuffer is a secondary command buffer, there must not be an outstanding cmdDebugMarkerBeginEXT command recorded to commandBuffer that has not previously been ended by a call to cmdDebugMarkerEndEXT

Valid Usage (Implicit)

Host Synchronization

  • Host access to commandBuffer must be externally synchronized
  • Host access to the CommandPool that commandBuffer was allocated from must be externally synchronized

Return Codes

Success
Failure

See Also

CommandBuffer

resetCommandBuffer Source #

Arguments

:: forall io. MonadIO io 
=> CommandBuffer

commandBuffer is the command buffer to reset. The command buffer can be in any state other than pending, and is moved into the initial state.

-> CommandBufferResetFlags

flags is a bitmask of CommandBufferResetFlagBits controlling the reset operation.

-> io () 

vkResetCommandBuffer - Reset a command buffer to the initial state

Description

Any primary command buffer that is in the recording or executable state and has commandBuffer recorded into it, becomes invalid.

Valid Usage

Valid Usage (Implicit)

Host Synchronization

  • Host access to commandBuffer must be externally synchronized

Return Codes

Success
Failure

See Also

CommandBuffer, CommandBufferResetFlags

data CommandBufferAllocateInfo Source #

VkCommandBufferAllocateInfo - Structure specifying the allocation parameters for command buffer object

Valid Usage (Implicit)

See Also

CommandBufferLevel, CommandPool, StructureType, allocateCommandBuffers

Constructors

CommandBufferAllocateInfo 

Fields

Instances

Instances details
Eq CommandBufferAllocateInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

Show CommandBufferAllocateInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

Generic CommandBufferAllocateInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

Associated Types

type Rep CommandBufferAllocateInfo :: Type -> Type #

Storable CommandBufferAllocateInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

FromCStruct CommandBufferAllocateInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

ToCStruct CommandBufferAllocateInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

Zero CommandBufferAllocateInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

type Rep CommandBufferAllocateInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

type Rep CommandBufferAllocateInfo = D1 ('MetaData "CommandBufferAllocateInfo" "Vulkan.Core10.CommandBuffer" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "CommandBufferAllocateInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "commandPool") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommandPool) :*: (S1 ('MetaSel ('Just "level") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommandBufferLevel) :*: S1 ('MetaSel ('Just "commandBufferCount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Word32))))

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

VkCommandBufferInheritanceInfo - Structure specifying command buffer inheritance info

Valid Usage

Valid Usage (Implicit)

See Also

Bool32, CommandBufferBeginInfo, Framebuffer, QueryControlFlags, QueryPipelineStatisticFlags, RenderPass, StructureType

Constructors

CommandBufferInheritanceInfo 

Fields

  • next :: Chain es

    pNext is NULL or a pointer to an extension-specific structure.

  • renderPass :: RenderPass

    renderPass is a RenderPass object defining which render passes the CommandBuffer will be compatible with and can be executed within. If the CommandBuffer will not be executed within a render pass instance, renderPass is ignored.

  • subpass :: Word32

    subpass is the index of the subpass within the render pass instance that the CommandBuffer will be executed within. If the CommandBuffer will not be executed within a render pass instance, subpass is ignored.

  • framebuffer :: Framebuffer

    framebuffer optionally refers to the Framebuffer object that the CommandBuffer will be rendering to if it is executed within a render pass instance. It can be NULL_HANDLE if the framebuffer is not known, or if the CommandBuffer will not be executed within a render pass instance.

    Note

    Specifying the exact framebuffer that the secondary command buffer will be executed with may result in better performance at command buffer execution time.

  • occlusionQueryEnable :: Bool

    occlusionQueryEnable specifies whether the command buffer can be executed while an occlusion query is active in the primary command buffer. If this is TRUE, then this command buffer can be executed whether the primary command buffer has an occlusion query active or not. If this is FALSE, then the primary command buffer must not have an occlusion query active.

  • queryFlags :: QueryControlFlags

    queryFlags specifies the query flags that can be used by an active occlusion query in the primary command buffer when this secondary command buffer is executed. If this value includes the QUERY_CONTROL_PRECISE_BIT bit, then the active query can return boolean results or actual sample counts. If this bit is not set, then the active query must not use the QUERY_CONTROL_PRECISE_BIT bit.

  • pipelineStatistics :: QueryPipelineStatisticFlags

    pipelineStatistics is a bitmask of QueryPipelineStatisticFlagBits specifying the set of pipeline statistics that can be counted by an active query in the primary command buffer when this secondary command buffer is executed. If this value includes a given bit, then this command buffer can be executed whether the primary command buffer has a pipeline statistics query active that includes this bit or not. If this value excludes a given bit, then the active pipeline statistics query must not be from a query pool that counts that statistic.

Instances

Instances details
Extensible CommandBufferInheritanceInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.CommandBuffer

Generic (CommandBufferInheritanceInfo es) Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

Associated Types

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

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

Defined in Vulkan.Core10.CommandBuffer

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

Defined in Vulkan.Core10.CommandBuffer

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

Defined in Vulkan.Core10.CommandBuffer

type Rep (CommandBufferInheritanceInfo es) Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

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

VkCommandBufferBeginInfo - Structure specifying a command buffer begin operation

Valid Usage

Valid Usage (Implicit)

See Also

CommandBufferInheritanceInfo, CommandBufferUsageFlags, StructureType, beginCommandBuffer

Constructors

CommandBufferBeginInfo 

Fields

Instances

Instances details
Extensible CommandBufferBeginInfo Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.CommandBuffer

Generic (CommandBufferBeginInfo es) Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

Associated Types

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

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

Defined in Vulkan.Core10.CommandBuffer

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

Defined in Vulkan.Core10.CommandBuffer

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

Defined in Vulkan.Core10.CommandBuffer

type Rep (CommandBufferBeginInfo es) Source # 
Instance details

Defined in Vulkan.Core10.CommandBuffer

type Rep (CommandBufferBeginInfo es) = D1 ('MetaData "CommandBufferBeginInfo" "Vulkan.Core10.CommandBuffer" "vulkan-3.3.1-inplace" 'False) (C1 ('MetaCons "CommandBufferBeginInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "next") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Chain es)) :*: (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CommandBufferUsageFlags) :*: S1 ('MetaSel ('Just "inheritanceInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe (SomeStruct CommandBufferInheritanceInfo))))))