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

Vulkan.Core10.Event

Synopsis

Documentation

createEvent Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that creates the event.

-> EventCreateInfo

pCreateInfo is a pointer to a EventCreateInfo structure containing information about how the event is to be created.

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

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

-> io Event 

vkCreateEvent - Create a new event object

Description

When created, the event object is in the unsignaled state.

Valid Usage

Valid Usage (Implicit)

  • device must be a valid Device handle
  • pCreateInfo must be a valid pointer to a valid EventCreateInfo structure
  • If pAllocator is not NULL, pAllocator must be a valid pointer to a valid AllocationCallbacks structure
  • pEvent must be a valid pointer to a Event handle

Return Codes

Success
Failure

See Also

VK_VERSION_1_0, AllocationCallbacks, Device, Event, EventCreateInfo

withEvent :: forall io r. MonadIO io => Device -> EventCreateInfo -> Maybe AllocationCallbacks -> (io Event -> (Event -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createEvent and destroyEvent

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

destroyEvent Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that destroys the event.

-> Event

event is the handle of the event to destroy.

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

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

-> io () 

vkDestroyEvent - Destroy an event object

Valid Usage

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

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to event must be externally synchronized

See Also

VK_VERSION_1_0, AllocationCallbacks, Device, Event

getEventStatus Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the event.

device must be a valid Device handle

-> Event

event is the handle of the event to query.

event must not have been created with EVENT_CREATE_DEVICE_ONLY_BIT_KHR

event must be a valid Event handle

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

-> io Result 

vkGetEventStatus - Retrieve the status of an event object

Description

Upon success, getEventStatus returns the state of the event object with the following return codes:

StatusMeaning
EVENT_SET The event specified by event is signaled.
EVENT_RESET The event specified by event is unsignaled.

Event Object Status Codes

If a cmdSetEvent or cmdResetEvent command is in a command buffer that is in the pending state, then the value returned by this command may immediately be out of date.

The state of an event can be updated by the host. The state of the event is immediately changed, and subsequent calls to getEventStatus will return the new state. If an event is already in the requested state, then updating it to the same state has no effect.

Return Codes

Success
Failure

See Also

VK_VERSION_1_0, Device, Event

setEvent Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the event.

-> Event

event is the event to set.

-> io () 

vkSetEvent - Set an event to signaled state

Description

When setEvent is executed on the host, it defines an /event signal operation/ which sets the event to the signaled state.

If event is already in the signaled state when setEvent is executed, then setEvent has no effect, and no event signal operation occurs.

Valid Usage

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to event must be externally synchronized

Return Codes

Success
Failure

See Also

VK_VERSION_1_0, Device, Event

resetEvent Source #

Arguments

:: forall io. MonadIO io 
=> Device

device is the logical device that owns the event.

-> Event

event is the event to reset.

-> io () 

vkResetEvent - Reset an event to non-signaled state

Description

When resetEvent is executed on the host, it defines an /event unsignal operation/ which resets the event to the unsignaled state.

If event is already in the unsignaled state when resetEvent is executed, then resetEvent has no effect, and no event unsignal operation occurs.

Valid Usage

  • There must be an execution dependency between resetEvent and the execution of any cmdWaitEvents that includes event in its pEvents parameter

Valid Usage (Implicit)

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

Host Synchronization

  • Host access to event must be externally synchronized

Return Codes

Success
Failure

See Also

VK_VERSION_1_0, Device, Event

data EventCreateInfo Source #

VkEventCreateInfo - Structure specifying parameters of a newly created event

Valid Usage (Implicit)

See Also

VK_VERSION_1_0, EventCreateFlags, StructureType, createEvent

Constructors

EventCreateInfo 

Fields

Instances

Instances details
Eq EventCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Event

Show EventCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Event

Storable EventCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Event

FromCStruct EventCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Event

ToCStruct EventCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Event

Zero EventCreateInfo Source # 
Instance details

Defined in Vulkan.Core10.Event

newtype Event Source #

Constructors

Event Word64 

Instances

Instances details
Eq Event Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Ord Event Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

compare :: Event -> Event -> Ordering #

(<) :: Event -> Event -> Bool #

(<=) :: Event -> Event -> Bool #

(>) :: Event -> Event -> Bool #

(>=) :: Event -> Event -> Bool #

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Show Event Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Storable Event Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

sizeOf :: Event -> Int #

alignment :: Event -> Int #

peekElemOff :: Ptr Event -> Int -> IO Event #

pokeElemOff :: Ptr Event -> Int -> Event -> IO () #

peekByteOff :: Ptr b -> Int -> IO Event #

pokeByteOff :: Ptr b -> Int -> Event -> IO () #

peek :: Ptr Event -> IO Event #

poke :: Ptr Event -> Event -> IO () #

Zero Event Source # 
Instance details

Defined in Vulkan.Core10.Handles

Methods

zero :: Event Source #

HasObjectType Event Source # 
Instance details

Defined in Vulkan.Core10.Handles

IsHandle Event Source # 
Instance details

Defined in Vulkan.Core10.Handles

newtype EventCreateFlagBits Source #

VkEventCreateFlagBits - Event creation flag bits

See Also

VK_VERSION_1_0, EventCreateFlags

Bundled Patterns

pattern EVENT_CREATE_DEVICE_ONLY_BIT_KHR :: EventCreateFlagBits

EVENT_CREATE_DEVICE_ONLY_BIT_KHR specifies that host event commands will not be used with this event.

Instances

Instances details
Eq EventCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.EventCreateFlagBits

Ord EventCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.EventCreateFlagBits

Read EventCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.EventCreateFlagBits

Show EventCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.EventCreateFlagBits

Storable EventCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.EventCreateFlagBits

Bits EventCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.EventCreateFlagBits

FiniteBits EventCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.EventCreateFlagBits

Zero EventCreateFlagBits Source # 
Instance details

Defined in Vulkan.Core10.Enums.EventCreateFlagBits