openxr-0.1: Bindings to the OpenXR API
Safe HaskellNone
LanguageHaskell2010

OpenXR.Core10.DisplayTiming

Synopsis

Documentation

beginFrame Source #

Arguments

:: forall io. MonadIO io 
=> Session

session is a valid Session handle.

-> ("frameBeginInfo" ::: Maybe FrameBeginInfo)

frameBeginInfo exists for extensibility purposes, it is NULL or a pointer to a valid FrameBeginInfo.

-> io Result 

xrBeginFrame - Marks a frame

Parameter Descriptions

Description

beginFrame is called prior to the start of frame rendering. The application should still call beginFrame but omit rendering work for the frame if FrameState::shouldRender is FALSE.

The runtime must return the error code ERROR_CALL_ORDER_INVALID if there was no corresponding successful call to waitFrame.

The runtime must return the success code FRAME_DISCARDED if a prior beginFrame has been called without an intervening call to endFrame.

The runtime must return ERROR_SESSION_NOT_RUNNING if the session is not running.

Valid Usage (Implicit)

  • session must be a valid Session handle
  • If frameBeginInfo is not NULL, frameBeginInfo must be a pointer to a valid FrameBeginInfo structure

Return Codes

Success
Failure

See Also

FrameBeginInfo, Session, endFrame, waitFrame

useFrame :: forall a io r. (Extendss FrameEndInfo a, PokeChain a, MonadIO io) => Session -> Maybe FrameBeginInfo -> FrameEndInfo a -> (Result -> io r) -> io (Result, r) Source #

This function will call the supplied action between calls to beginFrame and endFrame

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

locateViews :: forall io. MonadIO io => Session -> ViewLocateInfo -> io (Result, ViewState, "views" ::: Vector View) Source #

xrLocateViews - Gets view and projection info

Parameter Descriptions

  • session is a handle to the provided Session.
  • viewLocateInfo is a pointer to a valid ViewLocateInfo structure.
  • viewState is the output structure with the viewer state information.
  • viewCapacityInput is an input parameter which specifies the capacity of the views array. The required capacity must be same as defined by the corresponding ViewConfigurationType.
  • viewCountOutput is an output parameter which identifies the valid count of views.
  • views is an array of View.
  • See Buffer Size Parameters chapter for a detailed description of retrieving the required views size.

Description

The locateViews function returns the view and projection info for a particular display time. This time is typically the target display time for a given frame. Repeatedly calling locateViews with the same time may not necessarily return the same result. Instead the prediction gets increasingly accurate as the function is called closer to the given time for which a prediction is made. This allows an application to get the predicted views as late as possible in its pipeline to get the least amount of latency and prediction error.

locateViews returns an array of View elements, one for each view of the specified view configuration type, along with an ViewState containing additional state data shared across all views. The eye each view corresponds to is statically defined in https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#view_configuration_type in case the application wants to apply eye-specific rendering traits. The ViewState and View member data may change on subsequent calls to locateViews, and so applications must not assume it to be constant.

Valid Usage (Implicit)

  • session must be a valid Session handle
  • viewLocateInfo must be a pointer to a valid ViewLocateInfo structure
  • viewState must be a pointer to an ViewState structure
  • viewCountOutput must be a pointer to a uint32_t value
  • If viewCapacityInput is not 0, views must be a pointer to an array of viewCapacityInput View structures

Return Codes

Success
Failure

See Also

Session, View, ViewLocateInfo, ViewState

endFrame Source #

Arguments

:: forall a io. (Extendss FrameEndInfo a, PokeChain a, MonadIO io) 
=> Session

session is a valid Session handle.

session must be a valid Session handle

-> FrameEndInfo a

frameEndInfo is a pointer to a valid FrameEndInfo.

frameEndInfo must be a pointer to a valid FrameEndInfo structure

-> io Result 

xrEndFrame - Marks a frame

Parameter Descriptions

Description

endFrame may return immediately to the application. FrameEndInfo::displayTime should be computed using values returned by waitFrame. The runtime should be robust against variations in the timing of calls to waitFrame, since a pipelined system may call waitFrame on a separate thread from beginFrame and endFrame without any synchronization guarantees.

Note

An accurate predicted display time is very important to avoid black pull-in by reprojection and to reduce motion judder in case the runtime does not implement a translational reprojection. Reprojection should never display images before the display refresh period they were predicted for, even if they are completed early, because this will cause motion judder just the same. In other words, the better the predicted display time, the less latency experienced by the user.

Every call to endFrame must be preceded by a successful call to beginFrame. Failure to do so must result in ERROR_CALL_ORDER_INVALID being returned by endFrame. FrameEndInfo may reference swapchains into which the application has rendered for this frame. From each Swapchain only one image index is implicitly referenced per frame, the one corresponding to the last call to releaseSwapchainImage. However, a specific swapchain (and by extension a specific swapchain image index) may be referenced in FrameEndInfo multiple times. This can be used for example to render a side by side image into a single swapchain image and referencing it twice with differing image rectangles in different layers.

If no layers are provided then the display must be cleared.

ERROR_LAYER_INVALID must be returned if an unknown, unsupported layer type, or NULL pointer is passed as one of the FrameEndInfo::layers.

ERROR_LAYER_INVALID must be returned if a layer references a swapchain that has no released swapchain image.

ERROR_LAYER_LIMIT_EXCEEDED must be returned if FrameEndInfo::layerCount exceeds SystemGraphicsProperties::maxLayerCount or if the runtime is unable to composite the specified layers due to resource constraints.

ERROR_SWAPCHAIN_RECT_INVALID must be returned if FrameEndInfo::layers contains a composition layer which references pixels outside of the associated swapchain image or if negatively sized.

ERROR_ENVIRONMENT_BLEND_MODE_UNSUPPORTED must be returned if FrameEndInfo::environmentBlendMode is not supported.

ERROR_SESSION_NOT_RUNNING must be returned if the session is not running.

Note

Applications should discard frames for which endFrame returns a recoverable error over attempting to resubmit the frame with different frame parameters to provide a more consistent experience across different runtime implementations.

Return Codes

Success
Failure

See Also

FrameEndInfo, Session, beginFrame, waitFrame

waitFrame Source #

Arguments

:: forall a io. (Extendss FrameState a, PokeChain a, PeekChain a, MonadIO io) 
=> Session

session is a valid Session handle.

-> ("frameWaitInfo" ::: Maybe FrameWaitInfo)

frameWaitInfo exists for extensibility purposes, it is NULL or a pointer to a valid FrameWaitInfo.

-> io (Result, FrameState a) 

xrWaitFrame - Frame timing function

Parameter Descriptions

Description

waitFrame throttles the application frame loop in order to synchronize application frame submissions with the display. waitFrame returns a predicted display time for the next time that the runtime predicts a composited frame will be displayed. The runtime may affect this computation by changing the return values and throttling of waitFrame in response to feedback from frame submission and completion times in endFrame. An application must eventually match each waitFrame call with one call to beginFrame. A subsequent waitFrame call must block until the previous frame has been begun with beginFrame and must unblock independently of the corresponding call to endFrame. When less than one frame interval has passed since the previous return from waitFrame, the runtime should block until the beginning of the next frame interval. If more than one frame interval has passed since the last return from waitFrame, the runtime may return immediately or block until the beginning of the next frame interval.

In the case that an application has pipelined frame submissions, the application should compute the appropriate target display time using both the predicted display time and predicted display interval. The application should use the computed target display time when requesting space and view locations for rendering.

The FrameState::predictedDisplayTime returned by waitFrame must be monotonically increasing.

The runtime may dynamically adjust the start time of the frame interval relative to the display hardware’s refresh cycle to minimize graphics processor contention between the application and the compositor.

waitFrame must be callable from any thread, including a different thread than beginFrame/endFrame are being called from.

Calling waitFrame must be externally synchronized by the application, concurrent calls may result in undefined behavior.

The runtime must return ERROR_SESSION_NOT_RUNNING if the session is not running.

Note

The engine simulation should advance based on the display time. Every stage in the engine pipeline should use the exact same display time for one particular application-generated frame. An accurate and consistent display time across all stages and threads in the engine pipeline is important to avoid object motion judder. If the application has multiple pipeline stages, the application should pass its computed display time through its pipeline, as waitFrame must be called only once per frame.

Valid Usage (Implicit)

  • session must be a valid Session handle
  • If frameWaitInfo is not NULL, frameWaitInfo must be a pointer to a valid FrameWaitInfo structure
  • frameState must be a pointer to an FrameState structure

Thread Safety

  • Access to the session parameter by any other waitFrame call must be externally synchronized

Return Codes

Success
Failure

See Also

FrameState, FrameWaitInfo, Session, beginFrame, endFrame

waitFrameSafe Source #

Arguments

:: forall a io. (Extendss FrameState a, PokeChain a, PeekChain a, MonadIO io) 
=> Session

session is a valid Session handle.

-> ("frameWaitInfo" ::: Maybe FrameWaitInfo)

frameWaitInfo exists for extensibility purposes, it is NULL or a pointer to a valid FrameWaitInfo.

-> io (Result, FrameState a) 

A variant of waitFrame which makes a *safe* FFI call

data View Source #

XrView - Struct containing view projection state

Member Descriptions

Description

The View structure contains view pose and projection state necessary to render a single projection view in the view configuration.

Valid Usage (Implicit)

See Also

Fovf, Posef, StructureType, ViewLocateInfo, ViewState, locateViews

Constructors

View 

Fields

  • pose :: Posef

    pose is an Posef defining the location and orientation of the view in the space specified by the locateViews function.

  • fov :: Fovf

    fov is the Fovf for the four sides of the projection.

Instances

Instances details
Show View Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Methods

showsPrec :: Int -> View -> ShowS #

show :: View -> String #

showList :: [View] -> ShowS #

Storable View Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Methods

sizeOf :: View -> Int #

alignment :: View -> Int #

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

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

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

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

peek :: Ptr View -> IO View #

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

Zero View Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Methods

zero :: View #

ToCStruct View Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Methods

withCStruct :: View -> (Ptr View -> IO b) -> IO b #

pokeCStruct :: Ptr View -> View -> IO b -> IO b #

withZeroCStruct :: (Ptr View -> IO b) -> IO b #

pokeZeroCStruct :: Ptr View -> IO b -> IO b #

cStructSize :: Int #

cStructAlignment :: Int #

FromCStruct View Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Methods

peekCStruct :: Ptr View -> IO View #

data ViewLocateInfo Source #

XrViewLocateInfo - Struct containing view locate information

Member Descriptions

Description

The ViewLocateInfo structure contains the display time and space used to locate the view View structures.

The runtime must return error ERROR_VIEW_CONFIGURATION_TYPE_UNSUPPORTED if the given viewConfigurationType is not one of the supported type reported by enumerateViewConfigurations.

Valid Usage (Implicit)

See Also

Space, StructureType, https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrTime, View, ViewConfigurationType, ViewState, locateViews

Constructors

ViewLocateInfo 

Fields

Instances

Instances details
Eq ViewLocateInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Show ViewLocateInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Storable ViewLocateInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Zero ViewLocateInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

ToCStruct ViewLocateInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

FromCStruct ViewLocateInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

data ViewState Source #

XrViewState - Struct containing additional view state

Member Descriptions

Description

The ViewState contains additional view state from locateViews common to all views of the active view configuration.

Valid Usage (Implicit)

See Also

StructureType, View, ViewStateFlags, locateViews

Constructors

ViewState 

Fields

data FrameBeginInfo Source #

XrFrameBeginInfo - Begin frame information

Member Descriptions

Description

Because this structure only exists to support extension-specific structures, beginFrame will accept a NULL argument for frameBeginInfo for applications that are not using any relevant extensions.

Valid Usage (Implicit)

See Also

StructureType, beginFrame, waitFrame

Constructors

FrameBeginInfo 

Instances

Instances details
Eq FrameBeginInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Show FrameBeginInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Storable FrameBeginInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Zero FrameBeginInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

ToCStruct FrameBeginInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

FromCStruct FrameBeginInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

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

XrFrameEndInfo - End frame information

Valid Usage (Implicit)

See Also

CompositionLayerBaseHeader, EnvironmentBlendMode, StructureType, https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrTime, endFrame

Constructors

FrameEndInfo 

Fields

Instances

Instances details
Extensible FrameEndInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Methods

extensibleTypeName :: String Source #

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

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

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

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

Defined in OpenXR.Core10.DisplayTiming

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

Defined in OpenXR.Core10.DisplayTiming

Methods

zero :: FrameEndInfo es #

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

Defined in OpenXR.Core10.DisplayTiming

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

Defined in OpenXR.Core10.DisplayTiming

Methods

peekCStruct :: Ptr (FrameEndInfo es) -> IO (FrameEndInfo es) #

data FrameWaitInfo Source #

XrFrameWaitInfo - Wait frame information structure

Member Descriptions

Description

Because this structure only exists to support extension-specific structures, waitFrame must accept a NULL argument for frameWaitInfo for applications that are not using any relevant extensions.

Valid Usage (Implicit)

See Also

FrameState, StructureType, waitFrame

Constructors

FrameWaitInfo 

Instances

Instances details
Eq FrameWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Show FrameWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Storable FrameWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Zero FrameWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Methods

zero :: FrameWaitInfo #

ToCStruct FrameWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

FromCStruct FrameWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

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

XrFrameState - Frame prediction structure

Member Descriptions

Description

FrameState describes the time at which the next frame will be displayed to the user. predictedDisplayTime must refer to the midpoint of the interval during which the frame is displayed. The runtime may report a different predictedDisplayPeriod from the hardware’s refresh cycle.

For any frame where shouldRender is FALSE, the application should avoid heavy GPU work for that frame, for example by not rendering its layers. This typically happens when the application is transitioning into or out of a running session, or when some system UI is fully covering the application at the moment. As long as the session is running, the application should keep running the frame loop to maintain the frame synchronization to the runtime, even if this requires calling endFrame with all layers omitted.

Valid Usage (Implicit)

See Also

https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrBool32, https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrDuration, FrameWaitInfo, StructureType, https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrTime, waitFrame

Constructors

FrameState 

Fields

Instances

Instances details
Extensible FrameState Source # 
Instance details

Defined in OpenXR.Core10.DisplayTiming

Methods

extensibleTypeName :: String Source #

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

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

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

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

Defined in OpenXR.Core10.DisplayTiming

Methods

showsPrec :: Int -> FrameState es -> ShowS #

show :: FrameState es -> String #

showList :: [FrameState es] -> ShowS #

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

Defined in OpenXR.Core10.DisplayTiming

Methods

zero :: FrameState es #

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

Defined in OpenXR.Core10.DisplayTiming

Methods

withCStruct :: FrameState es -> (Ptr (FrameState es) -> IO b) -> IO b #

pokeCStruct :: Ptr (FrameState es) -> FrameState es -> IO b -> IO b #

withZeroCStruct :: (Ptr (FrameState es) -> IO b) -> IO b #

pokeZeroCStruct :: Ptr (FrameState es) -> IO b -> IO b #

cStructSize :: Int #

cStructAlignment :: Int #

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

Defined in OpenXR.Core10.DisplayTiming

Methods

peekCStruct :: Ptr (FrameState es) -> IO (FrameState es) #