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

Vulkan.Core10.Fence

Synopsis

Documentation

createFence :: forall a io. (Extendss FenceCreateInfo a, PokeChain a, MonadIO io) => Device -> FenceCreateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io Fence Source #

vkCreateFence - Create a new fence object

Parameters

  • device is the logical device that creates the fence.
  • pCreateInfo is a pointer to a FenceCreateInfo structure containing information about how the fence is to be created.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.
  • pFence is a pointer to a handle in which the resulting fence object is returned.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pCreateInfo must be a valid pointer to a valid FenceCreateInfo structure
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • pFence must be a valid pointer to a Fence handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, Fence, FenceCreateInfo

withFence :: forall a io r. (Extendss FenceCreateInfo a, PokeChain a, MonadIO io) => Device -> FenceCreateInfo a -> Maybe AllocationCallbacks -> (io Fence -> (Fence -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createFence and destroyFence

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

destroyFence :: forall io. MonadIO io => Device -> Fence -> ("allocator" ::: Maybe AllocationCallbacks) -> io () Source #

vkDestroyFence - Destroy a fence object

Parameters

  • device is the logical device that destroys the fence.
  • fence is the handle of the fence to destroy.
  • pAllocator controls host memory allocation as described in the Memory Allocation chapter.

Valid Usage

  • If AllocationCallbacks were provided when fence was created, a compatible set of callbacks must be provided here
  • If no AllocationCallbacks were provided when fence was created, pAllocator must be NULL

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to fence must be externally synchronized

See Also

AllocationCallbacks, Device, Fence

resetFences :: forall io. MonadIO io => Device -> ("fences" ::: Vector Fence) -> io () Source #

vkResetFences - Resets one or more fence objects

Parameters

  • device is the logical device that owns the fences.
  • fenceCount is the number of fences to reset.
  • pFences is a pointer to an array of fence handles to reset.

Description

If any member of pFences currently has its payload imported with temporary permanence, that fence’s prior permanent payload is first restored. The remaining operations described therefore operate on the restored payload.

When resetFences is executed on the host, it defines a /fence unsignal operation/ for each fence, which resets the fence to the unsignaled state.

If any member of pFences is already in the unsignaled state when resetFences is executed, then resetFences has no effect on that fence.

Valid Usage

  • Each element of pFences must not be currently associated with any queue command that has not yet completed execution on that queue

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pFences must be a valid pointer to an array of fenceCount valid Fence handles
  • fenceCount must be greater than 0
  • Each element of pFences must have been created, allocated, or retrieved from device

Host Synchronization

  • Host access to each member of pFences must be externally synchronized

Return Codes

Success
Failure

See Also

Device, Fence

getFenceStatus :: forall io. MonadIO io => Device -> Fence -> io Result Source #

vkGetFenceStatus - Return the status of a fence

Parameters

  • device is the logical device that owns the fence.
  • fence is the handle of the fence to query.

Description

Upon success, getFenceStatus returns the status of the fence object, with the following return codes:

Status Meaning
SUCCESS The fence specified by fence is signaled.
NOT_READY The fence specified by fence is unsignaled.
ERROR_DEVICE_LOST The device has been lost. See Lost Device.

Fence Object Status Codes

If a queue submission command is pending execution, then the value returned by this command may immediately be out of date.

If the device has been lost (see Lost Device), getFenceStatus may return any of the above status codes. If the device has been lost and getFenceStatus is called repeatedly, it will eventually return either SUCCESS or ERROR_DEVICE_LOST.

Return Codes

Success
Failure

See Also

Device, Fence

waitForFences :: forall io. MonadIO io => Device -> ("fences" ::: Vector Fence) -> ("waitAll" ::: Bool) -> ("timeout" ::: Word64) -> io Result Source #

vkWaitForFences - Wait for one or more fences to become signaled

Parameters

  • device is the logical device that owns the fences.
  • fenceCount is the number of fences to wait on.
  • pFences is a pointer to an array of fenceCount fence handles.
  • waitAll is the condition that must be satisfied to successfully unblock the wait. If waitAll is TRUE, then the condition is that all fences in pFences are signaled. Otherwise, the condition is that at least one fence in pFences is signaled.
  • timeout is the timeout period in units of nanoseconds. timeout is adjusted to the closest value allowed by the implementation-dependent timeout accuracy, which may be substantially longer than one nanosecond, and may be longer than the requested period.

Description

If the condition is satisfied when waitForFences is called, then waitForFences returns immediately. If the condition is not satisfied at the time waitForFences is called, then waitForFences will block and wait up to timeout nanoseconds for the condition to become satisfied.

If timeout is zero, then waitForFences does not wait, but simply returns the current state of the fences. TIMEOUT will be returned in this case if the condition is not satisfied, even though no actual wait was performed.

If the specified timeout period expires before the condition is satisfied, waitForFences returns TIMEOUT. If the condition is satisfied before timeout nanoseconds has expired, waitForFences returns SUCCESS.

If device loss occurs (see Lost Device) before the timeout has expired, waitForFences must return in finite time with either SUCCESS or ERROR_DEVICE_LOST.

Note

While we guarantee that waitForFences must return in finite time, no guarantees are made that it returns immediately upon device loss. However, the client can reasonably expect that the delay will be on the order of seconds and that calling waitForFences will not result in a permanently (or seemingly permanently) dead process.

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pFences must be a valid pointer to an array of fenceCount valid Fence handles
  • fenceCount must be greater than 0
  • Each element of pFences must have been created, allocated, or retrieved from device

Return Codes

Success
Failure

See Also

Bool32, Device, Fence

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

VkFenceCreateInfo - Structure specifying parameters of a newly created fence

Valid Usage (Implicit)

See Also

FenceCreateFlags, StructureType, createFence

Constructors

FenceCreateInfo 

Fields

Instances

Instances details
Extensible FenceCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Fence

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.Fence

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

Defined in Vulkan.Core10.Fence

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

Defined in Vulkan.Core10.Fence

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

Defined in Vulkan.Core10.Fence