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

OpenXR.Core10.Image

Synopsis

Documentation

enumerateSwapchainFormats :: forall io. MonadIO io => Session -> io (Result, "formats" ::: Vector Int64) Source #

xrEnumerateSwapchainFormats - Enumerates swapchain formats

Parameter Descriptions

  • session is the session that enumerates the supported formats.
  • formatCapacityInput is the capacity of the formats, or 0 to retrieve the required capacity.
  • formatCountOutput is a pointer to the count of uint64_t formats written, or a pointer to the required capacity in the case that formatCapacityInput is 0.
  • formats is a pointer to an array of int64_t format ids, but can be NULL if formatCapacityInput is 0. The format ids are specific to the specified graphics API.
  • See Buffer Size Parameters chapter for a detailed description of retrieving the required formats size.

Description

enumerateSwapchainFormats enumerates the texture formats supported by the current session. The type of formats returned are dependent on the graphics API specified in createSession. For example, if a DirectX graphics API was specified, then the enumerated formats correspond to the DXGI formats, such as DXGI_FORMAT_R8G8B8A8_UNORM_SRGB. Texture formats should be in order from highest to lowest runtime preference.

With an OpenGL-based graphics API, the texture formats correspond to OpenGL internal formats.

With a Direct3D-based graphics API, enumerateSwapchainFormats never returns typeless formats (e.g. DXGI_FORMAT_R8G8B8A8_TYPELESS). Only concrete formats are returned, and only concrete formats may be specified by applications for swapchain creation.

Runtimes must always return identical buffer contents from this enumeration for the lifetime of the session.

Valid Usage (Implicit)

  • session must be a valid Session handle
  • formatCountOutput must be a pointer to a uint32_t value
  • If formatCapacityInput is not 0, formats must be a pointer to an array of formatCapacityInput int64_t values

Return Codes

Success
Failure

See Also

Session, createSwapchain

createSwapchain Source #

Arguments

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

session is the session that creates the image.

session must be a valid Session handle

-> SwapchainCreateInfo a

createInfo is a pointer to an SwapchainCreateInfo structure containing parameters to be used to create the image.

createInfo must be a pointer to a valid SwapchainCreateInfo structure

-> io (Result, Swapchain) 

xrCreateSwapchain - Creates an XrSwapchain

Parameter Descriptions

Description

Creates an Swapchain handle. The returned swapchain handle may be subsequently used in API calls. Multiple Swapchain handles may exist simultaneously, up to some limit imposed by the runtime. The Swapchain handle must be eventually freed via the destroySwapchain function. The runtime must return ERROR_SWAPCHAIN_FORMAT_UNSUPPORTED if the image format specified in the SwapchainCreateInfo is unsupported. The runtime must return ERROR_FEATURE_UNSUPPORTED if any bit of the create flags specified in the SwapchainCreateInfo is unsupported.

Return Codes

Success
Failure

See Also

Session, Swapchain, SwapchainCreateInfo, acquireSwapchainImage, destroySwapchain, enumerateSwapchainFormats, enumerateSwapchainImages, releaseSwapchainImage

withSwapchain :: forall a io r. (Extendss SwapchainCreateInfo a, PokeChain a, MonadIO io) => Session -> SwapchainCreateInfo a -> (io (Result, Swapchain) -> ((Result, Swapchain) -> io ()) -> r) -> r Source #

A convenience wrapper to make a compatible pair of calls to createSwapchain and destroySwapchain

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

destroySwapchain Source #

Arguments

:: forall io. MonadIO io 
=> Swapchain

swapchain is the swapchain to destroy.

-> io () 

xrDestroySwapchain - Destroys an XrSwapchain

Parameter Descriptions

Description

All submitted graphics API commands that refer to swapchain must have completed execution. Runtimes may continue to utilize swapchain images after destroySwapchain is called.

Valid Usage (Implicit)

Thread Safety

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

Return Codes

Success
Failure

See Also

Swapchain, createSwapchain

enumerateSwapchainImages :: forall a io. (Inherits SwapchainImageBaseHeader a, ToCStruct a, FromCStruct a, MonadIO io) => Swapchain -> io (Result, "images" ::: Vector a) Source #

xrEnumerateSwapchainImages - Gets images from an XrSwapchain

Parameter Descriptions

  • swapchain is the Swapchain to get images from.
  • imageCapacityInput is the capacity of the images array, or 0 to indicate a request to retrieve the required capacity.
  • imageCountOutput is a pointer to the count of images written, or a pointer to the required capacity in the case that imageCapacityInput is 0.
  • images is a pointer to an array of graphics API-specific XrSwapchainImage structures based off of SwapchainImageBaseHeader. It can be NULL if imageCapacityInput is 0.
  • See Buffer Size Parameters chapter for a detailed description of retrieving the required images size.

Description

Fills an array of graphics API-specific XrSwapchainImage structures. The resources must be constant and valid for the lifetime of the Swapchain.

Runtimes must always return identical buffer contents from this enumeration for the lifetime of the swapchain.

Note: images is a pointer to an array of structures of graphics API-specific type, not an array of structure pointers.

Valid Usage (Implicit)

Return Codes

Success
Failure

See Also

Swapchain, SwapchainImageBaseHeader, createSwapchain

acquireSwapchainImage Source #

Arguments

:: forall io. MonadIO io 
=> Swapchain

swapchain is the swapchain from which to acquire an image.

-> ("acquireInfo" ::: Maybe SwapchainImageAcquireInfo)

acquireInfo exists for extensibility purposes, it is NULL or a pointer to a valid SwapchainImageAcquireInfo.

-> io (Result, "index" ::: Word32) 

xrAcquireSwapchainImage - Acquire a swapchain image

Parameter Descriptions

Description

Acquires the image corresponding to the index position in the array returned by enumerateSwapchainImages. The runtime must return ERROR_CALL_ORDER_INVALID if index has already been acquired and not yet released with releaseSwapchainImage. If the swapchain was created with the XR_SWAPCHAIN_CREATE_STATIC_IMAGE_BIT set in SwapchainCreateInfo::createFlags, this function must not have been previously called for this swapchain. The runtime must return ERROR_CALL_ORDER_INVALID if a swapchain created with the XR_SWAPCHAIN_CREATE_STATIC_IMAGE_BIT set in SwapchainCreateInfo::createFlags and this function has been successfully called previously for this swapchain.

Valid Usage (Implicit)

  • If acquireInfo is not NULL, acquireInfo must be a pointer to a valid SwapchainImageAcquireInfo structure
  • index must be a pointer to a uint32_t value

Return Codes

Success
Failure

See Also

Swapchain, SwapchainImageAcquireInfo, createSwapchain, destroySwapchain, enumerateSwapchainImages, releaseSwapchainImage, waitSwapchainImage

waitSwapchainImage Source #

Arguments

:: forall io. MonadIO io 
=> Swapchain

swapchain is the swapchain from which to wait for an image.

swapchain must be a valid Swapchain handle

-> SwapchainImageWaitInfo

waitInfo is a pointer to an SwapchainImageWaitInfo structure.

waitInfo must be a pointer to a valid SwapchainImageWaitInfo structure

-> io Result 

xrWaitSwapchainImage - Wait for a swapchain image to be available

Parameter Descriptions

Description

Before an application can begin writing to a swapchain image, it must first wait on the image to avoid writing to it before the compositor has finished reading from it. waitSwapchainImage will implicitly wait on the oldest acquired swapchain image which has not yet been successfully waited on. Once a swapchain image has been successfully waited on, it must be released before waiting on the next acquired swapchain image.

This function may block for longer than the timeout specified in SwapchainImageWaitInfo due to scheduling or contention.

If the timeout expires without the image becoming available for writing, TIMEOUT_EXPIRED must be returned. If waitSwapchainImage returns TIMEOUT_EXPIRED, the next call to waitSwapchainImage will wait on the same image index again until the function succeeds with SUCCESS. Note that this is not an error code; XR_SUCCEEDED(XR_TIMEOUT_EXPIRED) is true.

The runtime must return ERROR_CALL_ORDER_INVALID if no image has been acquired by calling acquireSwapchainImage.

Return Codes

Success
Failure

See Also

Swapchain, SwapchainImageWaitInfo, acquireSwapchainImage, createSwapchain, destroySwapchain, enumerateSwapchainImages, releaseSwapchainImage

waitSwapchainImageSafe Source #

Arguments

:: forall io. MonadIO io 
=> Swapchain

swapchain is the swapchain from which to wait for an image.

swapchain must be a valid Swapchain handle

-> SwapchainImageWaitInfo

waitInfo is a pointer to an SwapchainImageWaitInfo structure.

waitInfo must be a pointer to a valid SwapchainImageWaitInfo structure

-> io Result 

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

releaseSwapchainImage Source #

Arguments

:: forall io. MonadIO io 
=> Swapchain

swapchain is the Swapchain from which to release an image.

-> ("releaseInfo" ::: Maybe SwapchainImageReleaseInfo)

releaseInfo exists for extensibility purposes, it is NULL or a pointer to a valid SwapchainImageReleaseInfo.

-> io Result 

xrReleaseSwapchainImage - Release a swapchain image

Parameter Descriptions

Description

If the swapchain was created with the XR_SWAPCHAIN_CREATE_STATIC_IMAGE_BIT set in SwapchainCreateInfo::createFlags structure, this function must not have been previously called for this swapchain.

The runtime must return ERROR_CALL_ORDER_INVALID if no image has been waited on by calling waitSwapchainImage.

Valid Usage (Implicit)

Return Codes

Success
Failure

See Also

Swapchain, SwapchainImageReleaseInfo, acquireSwapchainImage, createSwapchain, destroySwapchain, enumerateSwapchainImages, waitSwapchainImage

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

Constructors

SwapchainCreateInfo 

Fields

  • next :: Chain es

    next is NULL or a pointer to the next structure in a structure chain. No such structures are defined in core OpenXR.

    next must be NULL or a valid pointer to the next structure in a structure chain. See also: SecondaryViewConfigurationSwapchainCreateInfoMSFT

  • createFlags :: SwapchainCreateFlags

    createFlags is a bitmask of XrSwapchainCreateFlagBits describing additional properties of the swapchain.

    createFlags must be 0 or a valid combination of XrSwapchainCreateFlagBits values

  • usageFlags :: SwapchainUsageFlags

    usageFlags is a bitmask of SwapchainUsageFlagBits describing the intended usage of the swapchain’s images. The usage flags define how the corresponding graphics API objects are created. A mismatch may result in swapchain images that do not support the application’s usage.

    usageFlags must be 0 or a valid combination of SwapchainUsageFlagBits values

  • format :: Int64

    format is a graphics API-specific texture format identifier. For example, if the graphics API specified in createSession is Vulkan, then this format is a Vulkan format such as VK_FORMAT_R8G8B8A8_SRGB. The format identifies the format that the runtime will interpret the texture as upon submission. Valid formats are indicated by enumerateSwapchainFormats.

  • sampleCount :: Word32

    sampleCount is the number of sub-data element samples in the image, must not be 0 or greater than the graphics API’s maximum limit.

  • width :: Word32

    width is the width of the image, must not be 0 or greater than the graphics API’s maximum limit.

  • height :: Word32

    height is the height of the image, must not be 0 or greater than the graphics API’s maximum limit.

  • faceCount :: Word32

    faceCount is the number of faces, which can be either 6 (for cubemaps) or 1.

  • arraySize :: Word32

    arraySize is the number of array layers in the image or 1 for a 2D image, must not be 0 or greater than the graphics API’s maximum limit.

  • mipCount :: Word32

    mipCount describes the number of levels of detail available for minified sampling of the image, must not be 0 or greater than the graphics API’s maximum limit.

Instances

Instances details
Extensible SwapchainCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Methods

extensibleTypeName :: String Source #

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

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

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

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

Defined in OpenXR.Core10.Image

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

Defined in OpenXR.Core10.Image

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

Defined in OpenXR.Core10.Image

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

Defined in OpenXR.Core10.Image

data SwapchainImageBaseHeader Source #

XrSwapchainImageBaseHeader - Image base header for a swapchain image

Member Descriptions

Description

The SwapchainImageBaseHeader is a base structure that can be overridden by a graphics API-specific XrSwapchainImage* child structure.

Valid Usage (Implicit)

See Also

StructureType, enumerateSwapchainImages

Constructors

SwapchainImageBaseHeader 

Fields

Instances

Instances details
Eq SwapchainImageBaseHeader Source # 
Instance details

Defined in OpenXR.Core10.Image

Show SwapchainImageBaseHeader Source # 
Instance details

Defined in OpenXR.Core10.Image

Storable SwapchainImageBaseHeader Source # 
Instance details

Defined in OpenXR.Core10.Image

Zero SwapchainImageBaseHeader Source # 
Instance details

Defined in OpenXR.Core10.Image

ToCStruct SwapchainImageBaseHeader Source # 
Instance details

Defined in OpenXR.Core10.Image

FromCStruct SwapchainImageBaseHeader Source # 
Instance details

Defined in OpenXR.Core10.Image

Inheritable SwapchainImageBaseHeader Source # 
Instance details

Defined in OpenXR.Core10.Image

data SwapchainImageAcquireInfo Source #

XrSwapchainImageAcquireInfo - Describes a swapchain image acquisition

Member Descriptions

Description

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

Valid Usage (Implicit)

See Also

StructureType, acquireSwapchainImage

Instances

Instances details
Eq SwapchainImageAcquireInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Show SwapchainImageAcquireInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Storable SwapchainImageAcquireInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Zero SwapchainImageAcquireInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

ToCStruct SwapchainImageAcquireInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

FromCStruct SwapchainImageAcquireInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

data SwapchainImageWaitInfo Source #

XrSwapchainImageWaitInfo - Describes a swapchain image wait operation

Valid Usage (Implicit)

See Also

https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrDuration, StructureType, waitSwapchainImage

Constructors

SwapchainImageWaitInfo 

Fields

  • timeout :: Duration

    timeout indicates how many nanoseconds the call should block waiting for the image to become available for writing.

Instances

Instances details
Eq SwapchainImageWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Show SwapchainImageWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Storable SwapchainImageWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Zero SwapchainImageWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

ToCStruct SwapchainImageWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

FromCStruct SwapchainImageWaitInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

data SwapchainImageReleaseInfo Source #

XrSwapchainImageReleaseInfo - Describes a swapchain image release

Member Descriptions

Description

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

Valid Usage (Implicit)

See Also

StructureType, releaseSwapchainImage

Instances

Instances details
Eq SwapchainImageReleaseInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Show SwapchainImageReleaseInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Storable SwapchainImageReleaseInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

Zero SwapchainImageReleaseInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

ToCStruct SwapchainImageReleaseInfo Source # 
Instance details

Defined in OpenXR.Core10.Image

FromCStruct SwapchainImageReleaseInfo Source # 
Instance details

Defined in OpenXR.Core10.Image