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

OpenXR.Core10.Space

Synopsis

Documentation

destroySpace Source #

Arguments

:: forall io. MonadIO io 
=> Space

space is a handle to an Space previously created by a function such as createReferenceSpace.

-> io () 

xrDestroySpace - Creates a space based on a pose action

Parameter Descriptions

Description

Space handles are destroyed using destroySpace. The runtime may still use this space if there are active dependencies (e.g, compositions in progress).

Valid Usage (Implicit)

  • space must be a valid Space handle

Thread Safety

  • Access to space, and any child handles, must be externally synchronized

Return Codes

Success
Failure

See Also

Space, createActionSpace, createReferenceSpace

enumerateReferenceSpaces :: forall io. MonadIO io => Session -> io (Result, "spaces" ::: Vector ReferenceSpaceType) Source #

xrEnumerateReferenceSpaces - Enumerate available reference spaces

Parameter Descriptions

  • spaceCapacityInput is the capacity of the spaces array, or 0 to indicate a request to retrieve the required capacity.
  • spaceCountOutput is a pointer to the count of spaces written, or a pointer to the required capacity in the case that spaceCapacityInput is 0.
  • spaces is a pointer to an application-allocated array that will be filled with the enumerant of each supported reference space. It can be NULL if spaceCapacityInput is 0.
  • See Buffer Size Parameters chapter for a detailed description of retrieving the required spaces size.

Description

Enumerates the set of reference space types that this runtime supports for a given session. Runtimes must always return identical buffer contents from this enumeration for the lifetime of the session.

If a session enumerates support for a given reference space type, calls to createReferenceSpace must succeed for that session, with any transient unavailability of poses expressed later during calls to locateSpace.

Valid Usage (Implicit)

  • session must be a valid Session handle
  • spaceCountOutput must be a pointer to a uint32_t value
  • If spaceCapacityInput is not 0, spaces must be a pointer to an array of spaceCapacityInput ReferenceSpaceType values

Return Codes

Success
Failure

See Also

ReferenceSpaceType, Session, Space

createReferenceSpace Source #

Arguments

:: forall io. MonadIO io 
=> Session

session is a handle to an Session previously created with createSession.

session must be a valid Session handle

-> ReferenceSpaceCreateInfo

createInfo is the ReferenceSpaceCreateInfo used to specify the space.

createInfo must be a pointer to a valid ReferenceSpaceCreateInfo structure

-> io (Result, Space) 

xrCreateReferenceSpace - Creates a reference space

Parameter Descriptions

Description

Creates an Space handle based on a chosen reference space. Application can provide an Posef to define the position and orientation of the new space’s origin within the natural reference frame of the reference space.

Multiple Space handles may exist simultaneously, up to some limit imposed by the runtime. The Space handle must be eventually freed via the destroySpace function.

The runtime must return ERROR_REFERENCE_SPACE_UNSUPPORTED if the given reference space type is not supported by this session.

Return Codes

Success
Failure

See Also

ReferenceSpaceCreateInfo, Session, Space, destroySpace

withReferenceSpace :: forall io r. MonadIO io => Session -> ReferenceSpaceCreateInfo -> (io (Result, Space) -> ((Result, Space) -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createReferenceSpace and destroySpace

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

createActionSpace Source #

Arguments

:: forall io. MonadIO io 
=> Session

session is the Session to create the action space in.

session must be a valid Session handle

-> ActionSpaceCreateInfo

createInfo is the ActionSpaceCreateInfo used to specify the space.

createInfo must be a pointer to a valid ActionSpaceCreateInfo structure

-> io (Result, Space) 

xrCreateActionSpace - Creates a space based on a pose action

Parameter Descriptions

Description

Creates an Space handle based on a chosen pose action. Application can provide an Posef to define the position and orientation of the new space’s origin within the natural reference frame of the action space.

Multiple Space handles may exist simultaneously, up to some limit imposed by the runtime. The Space handle must be eventually freed via the destroySpace function or by destroying the parent Action handle.

The runtime must return ERROR_ACTION_TYPE_MISMATCH if the action provided in action is not of type ACTION_TYPE_POSE_INPUT.

Return Codes

Success
Failure

See Also

ActionSpaceCreateInfo, Session, Space, destroySpace

withActionSpace :: forall io r. MonadIO io => Session -> ActionSpaceCreateInfo -> (io (Result, Space) -> ((Result, Space) -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createActionSpace and destroySpace

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

locateSpace Source #

Arguments

:: forall a io. (Extendss SpaceLocation a, PokeChain a, PeekChain a, MonadIO io) 
=> Space

space identifies the target space to locate.

-> ("baseSpace" ::: Space)

baseSpace identifies the underlying space in which to locate space.

-> Time

time is the time for which the location should be provided.

-> io (Result, SpaceLocation a) 

xrLocateSpace - Locates a space with reference to another space

Parameter Descriptions

Description

For a time in the past, the runtime should locate the spaces based on the runtime’s most accurate current understanding of how the world was at that historical time.

For a time in the future, the runtime should locate the spaces based on the runtime’s most up-to-date prediction of how the world will be at that future time.

The minimum valid range of values for time are described in https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#prediction-time-limits. For values of time outside this range, locateSpace may return a location with no position and XR_SPACE_LOCATION_POSITION_VALID_BIT unset.

Some devices improve their understanding of the world as the device is used. The location returned by locateSpace for a given space, baseSpace and time may change over time, even for spaces that track static objects, as one or both spaces adjust their origins.

During tracking loss of space relative to baseSpace, runtimes should continue to provide inferred or last-known position and orientation values. These inferred poses can, for example, be based on neck model updates, inertial dead reckoning, or a last-known position, so long as it is still reasonable for the application to use that pose. While a runtime is providing position data, it must continue to set XR_SPACE_LOCATION_POSITION_VALID_BIT but it can clear XR_SPACE_LOCATION_POSITION_TRACKED_BIT to indicate that the position is inferred or last-known in this way.

If the runtime has not yet observed even a last-known pose for how to locate space in baseSpace (e.g. one space is an action space bound to a motion controller that has not yet been detected, or the two spaces are in disconnected fragments of the runtime’s tracked volume), the runtime should return a location with no position and XR_SPACE_LOCATION_POSITION_VALID_BIT unset.

The runtime must return a location with both XR_SPACE_LOCATION_POSITION_VALID_BIT and XR_SPACE_LOCATION_POSITION_TRACKED_BIT set when locating space and baseSpace if both spaces were created relative to the same entity (e.g. two action spaces for the same action), even if the entity is currently untracked. The location in this case is the difference in the two spaces' application-specified transforms relative to that common entity.

The runtime should return a location with XR_SPACE_LOCATION_POSITION_VALID_BIT set and XR_SPACE_LOCATION_POSITION_TRACKED_BIT unset for spaces tracking two static entities in the world when their relative pose is known to the runtime. This enables applications to make use of the runtime’s latest knowledge of the world, even during tracking loss.

If an SpaceVelocity structure is chained to the next pointer of SpaceLocation and the velocity is observed or can be calculated by the runtime, the runtime must fill in the linear velocity of the origin of space within the reference frame of baseSpace and set the XR_SPACE_VELOCITY_LINEAR_VALID_BIT. Similarly, if an SpaceVelocity structure is chained to the next pointer of SpaceLocation and the angular velocity is observed or can be calculated by the runtime, the runtime must fill in the angular velocity of the origin of space within the reference frame of baseSpace and set the XR_SPACE_VELOCITY_ANGULAR_VALID_BIT.

The following example code shows how an application can get both the location and velocity of a space within a base space using the locateSpace function by chaining an SpaceVelocity to the next pointer of SpaceLocation and calling locateSpace.

XrSpace space;      // previously initialized
XrSpace baseSpace;  // previously initialized
XrTime time;        // previously initialized

XrSpaceVelocity velocity {XR_TYPE_SPACE_VELOCITY};
XrSpaceLocation location {XR_TYPE_SPACE_LOCATION, &velocity};
xrLocateSpace(space, baseSpace, time, &location);

Valid Usage (Implicit)

  • space must be a valid Space handle
  • baseSpace must be a valid Space handle
  • location must be a pointer to an SpaceLocation structure
  • Both of baseSpace and space must have been created, allocated, or retrieved from the same Session

Return Codes

Success
Failure

See Also

Space, SpaceLocation, XrSpaceLocationFlagBits, https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrTime

getReferenceSpaceBoundsRect Source #

Arguments

:: forall io. MonadIO io 
=> Session

session is a handle to an Session previously created with createSession.

session must be a valid Session handle

-> ReferenceSpaceType

referenceSpaceType is the reference space type whose bounds should be retrieved.

referenceSpaceType must be a valid ReferenceSpaceType value

-> io (Result, "bounds" ::: Extent2Df) 

data Vector3f Source #

XrVector3f - Three-dimensional vector

Member Descriptions

Description

If used to represent physical distances (rather than e.g. velocity or angular velocity) and not otherwise specified, values must be in meters.

See Also

HandJointVelocityEXT, HandMeshVertexMSFT, Posef, Quaternionf, SpaceVelocity, Vector2f, Vector4f

Constructors

Vector3f 

Fields

  • x :: Float

    x is the x coordinate of the vector.

  • y :: Float

    y is the y coordinate of the vector.

  • z :: Float

    z is the z coordinate of the vector.

Instances

Instances details
Eq Vector3f Source # 
Instance details

Defined in OpenXR.Core10.Space

Show Vector3f Source # 
Instance details

Defined in OpenXR.Core10.Space

Storable Vector3f Source # 
Instance details

Defined in OpenXR.Core10.Space

Zero Vector3f Source # 
Instance details

Defined in OpenXR.Core10.Space

Methods

zero :: Vector3f #

ToCStruct Vector3f Source # 
Instance details

Defined in OpenXR.Core10.Space

FromCStruct Vector3f Source # 
Instance details

Defined in OpenXR.Core10.Space

data Quaternionf Source #

XrQuaternionf - Unit Quaternion

Member Descriptions

See Also

CompositionLayerCubeKHR, Posef, Vector2f, Vector3f, Vector4f

Constructors

Quaternionf 

Fields

  • x :: Float

    x is the x coordinate of the quaternion.

  • y :: Float

    y is the y coordinate of the quaternion.

  • z :: Float

    z is the z coordinate of the quaternion.

  • w :: Float

    w is the w coordinate of the quaternion.

data Posef Source #

XrPosef - Location and orientation in a space.

Member Descriptions

A construct representing a position and orientation within a space, with position expressed in meters, and orientation represented as a unit quaternion. When using Posef the rotation described by orientation is always applied before the translation described by position.

Description

A runtime must return ERROR_POSE_INVALID if the orientation norm deviates by more than 1% from unit length.

See Also

ActionSpaceCreateInfo, CompositionLayerCylinderKHR, CompositionLayerEquirect2KHR, CompositionLayerEquirectKHR, CompositionLayerProjectionView, CompositionLayerQuad, ControllerModelNodeStateMSFT, EventDataReferenceSpaceChangePending, HandJointLocationEXT, HandMeshSpaceCreateInfoMSFT, Quaternionf, ReferenceSpaceCreateInfo, SpaceLocation, SpatialAnchorCreateInfoMSFT, SpatialAnchorSpaceCreateInfoMSFT, SpatialGraphNodeSpaceCreateInfoMSFT, Vector2f, Vector3f, Vector4f, View, xrSetInputDeviceLocationEXT

Constructors

Posef 

Fields

Instances

Instances details
Show Posef Source # 
Instance details

Defined in OpenXR.Core10.Space

Methods

showsPrec :: Int -> Posef -> ShowS #

show :: Posef -> String #

showList :: [Posef] -> ShowS #

Storable Posef Source # 
Instance details

Defined in OpenXR.Core10.Space

Methods

sizeOf :: Posef -> Int #

alignment :: Posef -> Int #

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

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

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

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

peek :: Ptr Posef -> IO Posef #

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

Zero Posef Source # 
Instance details

Defined in OpenXR.Core10.Space

Methods

zero :: Posef #

ToCStruct Posef Source # 
Instance details

Defined in OpenXR.Core10.Space

Methods

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

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

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

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

cStructSize :: Int #

cStructAlignment :: Int #

FromCStruct Posef Source # 
Instance details

Defined in OpenXR.Core10.Space

Methods

peekCStruct :: Ptr Posef -> IO Posef #

data ReferenceSpaceCreateInfo Source #

XrReferenceSpaceCreateInfo - Creation info for a reference space

Valid Usage (Implicit)

See Also

Posef, ReferenceSpaceType, Space, StructureType, createReferenceSpace

Constructors

ReferenceSpaceCreateInfo 

Fields

Instances

Instances details
Show ReferenceSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

Storable ReferenceSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

Zero ReferenceSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

ToCStruct ReferenceSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

FromCStruct ReferenceSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

data ActionSpaceCreateInfo Source #

XrActionSpaceCreateInfo - Creation info for an action space

Valid Usage (Implicit)

See Also

Action, https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrPath, Posef, Space, StructureType, createActionSpace

Constructors

ActionSpaceCreateInfo 

Fields

Instances

Instances details
Show ActionSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

Storable ActionSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

Zero ActionSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

ToCStruct ActionSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

FromCStruct ActionSpaceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Space

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

XrSpaceLocation - Contains info about a space

Valid Usage (Implicit)

See Also

Posef, Space, SpaceLocationFlags, SpaceVelocity, StructureType, locateSpace

Constructors

SpaceLocation 

Fields

Instances

Instances details
Extensible SpaceLocation Source # 
Instance details

Defined in OpenXR.Core10.Space

Methods

extensibleTypeName :: String Source #

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

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

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

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

Defined in OpenXR.Core10.Space

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

Defined in OpenXR.Core10.Space

Methods

zero :: SpaceLocation es #

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

Defined in OpenXR.Core10.Space

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

Defined in OpenXR.Core10.Space

data SpaceVelocity Source #

XrSpaceVelocity - Contains info about a space

Valid Usage (Implicit)

See Also

Space, SpaceLocation, SpaceVelocityFlags, StructureType, Vector3f, locateSpace

Constructors

SpaceVelocity 

Fields

  • velocityFlags :: SpaceVelocityFlags

    velocityFlags is a bitfield, with bit masks defined in XrSpaceVelocityFlagBits, to indicate which members contain valid data. If none of the bits are set, no other fields in this structure should be considered to be valid or meaningful.

    velocityFlags must be 0 or a valid combination of XrSpaceVelocityFlagBits values

  • linearVelocity :: Vector3f

    linearVelocity is the relative linear velocity of the origin of locateSpace::space with respect to and expressed in the reference frame of locateSpace::baseSpace, in units of meters per second.

  • angularVelocity :: Vector3f

    angularVelocity is the relative angular velocity of locateSpace::space with respect to locateSpace::baseSpace. The vector’s direction is expressed in the reference frame of locateSpace::baseSpace and is parallel to the rotational axis of locateSpace::space. The vector’s magnitude is the relative angular speed of locateSpace::space in radians per second. The vector follows the right-hand rule for torque/rotation.