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

Vulkan.Core10.QueueSemaphore

Synopsis

Documentation

createSemaphore Source #

Arguments

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

device is the logical device that creates the semaphore.

-> SemaphoreCreateInfo a

pCreateInfo is a pointer to a SemaphoreCreateInfo structure containing information about how the semaphore is to be created.

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

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

-> io Semaphore 

vkCreateSemaphore - Create a new queue semaphore object

Valid Usage (Implicit)

  • device must be a valid Device handle

Return Codes

Success
Failure

See Also

AllocationCallbacks, Device, Semaphore, SemaphoreCreateInfo

withSemaphore :: forall a io r. (Extendss SemaphoreCreateInfo a, PokeChain a, MonadIO io) => Device -> SemaphoreCreateInfo a -> Maybe AllocationCallbacks -> (io Semaphore -> (Semaphore -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createSemaphore and destroySemaphore

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

destroySemaphore Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the semaphore.

-> Semaphore

semaphore is the handle of the semaphore to destroy.

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

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

-> io () 

vkDestroySemaphore - Destroy a semaphore object

Valid Usage

  • All submitted batches that refer to semaphore must have completed execution
  • If AllocationCallbacks were provided when semaphore was created, a compatible set of callbacks must be provided here
  • If no AllocationCallbacks were provided when semaphore was created, pAllocator must be NULL

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to semaphore must be externally synchronized

See Also

AllocationCallbacks, Device, Semaphore

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

VkSemaphoreCreateInfo - Structure specifying parameters of a newly created semaphore

Valid Usage (Implicit)

See Also

SemaphoreCreateFlags, StructureType, createSemaphore

Constructors

SemaphoreCreateInfo 

Fields

Instances

Instances details
Extensible SemaphoreCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.QueueSemaphore

Methods

extensibleType :: StructureType Source #

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

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

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

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

Defined in Vulkan.Core10.QueueSemaphore

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

Defined in Vulkan.Core10.QueueSemaphore

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

Defined in Vulkan.Core10.QueueSemaphore

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

Defined in Vulkan.Core10.QueueSemaphore

newtype Semaphore Source #

Constructors

Semaphore Word64 

Instances

Instances details
Eq Semaphore Source # 
Instance details

Defined in Vulkan.Core10.Handles

Ord Semaphore Source # 
Instance details

Defined in Vulkan.Core10.Handles

Show Semaphore Source # 
Instance details

Defined in Vulkan.Core10.Handles

Storable Semaphore Source # 
Instance details

Defined in Vulkan.Core10.Handles

Zero Semaphore Source # 
Instance details

Defined in Vulkan.Core10.Handles

HasObjectType Semaphore Source # 
Instance details

Defined in Vulkan.Core10.Handles

IsHandle Semaphore Source # 
Instance details

Defined in Vulkan.Core10.Handles

newtype SemaphoreCreateFlags Source #

VkSemaphoreCreateFlags - Reserved for future use

Description

SemaphoreCreateFlags is a bitmask type for setting a mask, but is currently reserved for future use.

See Also

SemaphoreCreateInfo

Instances

Instances details
Eq SemaphoreCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.SemaphoreCreateFlags

Ord SemaphoreCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.SemaphoreCreateFlags

Read SemaphoreCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.SemaphoreCreateFlags

Show SemaphoreCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.SemaphoreCreateFlags

Storable SemaphoreCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.SemaphoreCreateFlags

Bits SemaphoreCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.SemaphoreCreateFlags

Zero SemaphoreCreateFlags Source # 
Instance details

Defined in Vulkan.Core10.Enums.SemaphoreCreateFlags