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

OpenXR.CStruct.Extends

Synopsis

Documentation

data BaseInStructure Source #

XrBaseInStructure - Convenience type for iterating (read only)

Member Descriptions

Description

BaseInStructure can be used to facilitate iterating through a read-only structure pointer chain.

See Also

BaseInStructure, BaseOutStructure, StructureType

Constructors

BaseInStructure 

Fields

Instances

Instances details
Eq BaseInStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Show BaseInStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Storable BaseInStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Zero BaseInStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

ToCStruct BaseInStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

FromCStruct BaseInStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

data BaseOutStructure Source #

XrBaseOutStructure - Convenience type for iterating (mutable)

Member Descriptions

Description

BaseOutStructure can be used to facilitate iterating through a structure pointer chain that returns data back to the application.

See Also

BaseInStructure, BaseOutStructure, StructureType

Constructors

BaseOutStructure 

Fields

Instances

Instances details
Eq BaseOutStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Show BaseOutStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Storable BaseOutStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Zero BaseOutStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

ToCStruct BaseOutStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

FromCStruct BaseOutStructure Source # 
Instance details

Defined in OpenXR.CStruct.Extends

type family Extends (a :: [Type] -> Type) (b :: Type) :: Constraint where ... Source #

Equations

Extends CompositionLayerBaseHeader CompositionLayerColorScaleBiasKHR = () 
Extends CompositionLayerProjectionView CompositionLayerDepthInfoKHR = () 
Extends FrameEndInfo SecondaryViewConfigurationFrameEndInfoMSFT = () 
Extends FrameState SecondaryViewConfigurationFrameStateMSFT = () 
Extends HandJointLocationsEXT HandJointVelocitiesEXT = () 
Extends HandTrackerCreateInfoEXT HandPoseTypeInfoMSFT = () 
Extends InstanceCreateInfo InstanceCreateInfoAndroidKHR = () 
Extends InstanceCreateInfo DebugUtilsMessengerCreateInfoEXT = () 
Extends InteractionProfileSuggestedBinding InteractionProfileAnalogThresholdVALVE = () 
Extends InteractionProfileSuggestedBinding BindingModificationsKHR = () 
Extends SessionBeginInfo SecondaryViewConfigurationSessionBeginInfoMSFT = () 
Extends SessionCreateInfo GraphicsBindingOpenGLWin32KHR = () 
Extends SessionCreateInfo GraphicsBindingOpenGLXlibKHR = () 
Extends SessionCreateInfo GraphicsBindingOpenGLXcbKHR = () 
Extends SessionCreateInfo GraphicsBindingOpenGLWaylandKHR = () 
Extends SessionCreateInfo GraphicsBindingD3D11KHR = () 
Extends SessionCreateInfo GraphicsBindingD3D12KHR = () 
Extends SessionCreateInfo GraphicsBindingOpenGLESAndroidKHR = () 
Extends SessionCreateInfo GraphicsBindingVulkanKHR = () 
Extends SessionCreateInfo SessionCreateInfoOverlayEXTX = () 
Extends SessionCreateInfo GraphicsBindingEGLMNDX = () 
Extends SessionCreateInfo HolographicWindowAttachmentMSFT = () 
Extends SpaceLocation SpaceVelocity = () 
Extends SpaceLocation EyeGazeSampleTimeEXT = () 
Extends SwapchainCreateInfo SecondaryViewConfigurationSwapchainCreateInfoMSFT = () 
Extends SystemProperties SystemEyeGazeInteractionPropertiesEXT = () 
Extends SystemProperties SystemHandTrackingPropertiesEXT = () 
Extends SystemProperties SystemHandTrackingMeshPropertiesMSFT = () 
Extends ViewConfigurationView ViewConfigurationDepthRangeEXT = () 
Extends ViewConfigurationView ViewConfigurationViewFovEPIC = () 
Extends a b = TypeError ((ShowType a :<>: Text " is not extended by ") :<>: ShowType b) 

class PeekChain es where Source #

Methods

peekChain :: Ptr (Chain es) -> IO (Chain es) Source #

Instances

Instances details
PeekChain ('[] :: [Type]) Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Methods

peekChain :: Ptr (Chain '[]) -> IO (Chain '[]) Source #

(FromCStruct e, PeekChain es) => PeekChain (e ': es) Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Methods

peekChain :: Ptr (Chain (e ': es)) -> IO (Chain (e ': es)) Source #

class PokeChain es where Source #

Methods

withChain :: Chain es -> (Ptr (Chain es) -> IO a) -> IO a Source #

withZeroChain :: (Ptr (Chain es) -> IO a) -> IO a Source #

Instances

Instances details
PokeChain ('[] :: [Type]) Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Methods

withChain :: Chain '[] -> (Ptr (Chain '[]) -> IO a) -> IO a Source #

withZeroChain :: (Ptr (Chain '[]) -> IO a) -> IO a Source #

(ToCStruct e, PokeChain es) => PokeChain (e ': es) Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Methods

withChain :: Chain (e ': es) -> (Ptr (Chain (e ': es)) -> IO a) -> IO a Source #

withZeroChain :: (Ptr (Chain (e ': es)) -> IO a) -> IO a Source #

type family Chain (xs :: [a]) = (r :: a) | r -> xs where ... Source #

Equations

Chain '[] = () 
Chain (x ': xs) = (x, Chain xs) 

type family Extendss (p :: [Type] -> Type) (xs :: [Type]) :: Constraint where ... Source #

Equations

Extendss p '[] = () 
Extendss p (x ': xs) = (Extends p x, Extendss p xs) 

data SomeStruct (a :: [Type] -> Type) where Source #

Constructors

SomeStruct :: forall a es. (Extendss a es, PokeChain es, Show (Chain es)) => a es -> SomeStruct a 

Instances

Instances details
(forall (es :: [Type]). Show (Chain es) => Show (a es)) => Show (SomeStruct a) Source # 
Instance details

Defined in OpenXR.CStruct.Extends

Zero (a ('[] :: [Type])) => Zero (SomeStruct a) Source #

The constraint is so on this instance to encourage type inference

Instance details

Defined in OpenXR.CStruct.Extends

Methods

zero :: SomeStruct a #

extendSomeStruct :: (Extensible a, Extends a e, ToCStruct e, Show e) => e -> SomeStruct a -> SomeStruct a Source #

Add an extension to the beginning of the struct chain

This can be used to optionally extend structs based on some condition (for example, an extension or layer being available)

withSomeStruct :: forall a b. SomeStruct a -> (forall es. (Extendss a es, PokeChain es, Show (Chain es)) => a es -> b) -> b Source #

Consume a SomeStruct value

withSomeCStruct :: forall a b. (forall es. (Extendss a es, PokeChain es) => ToCStruct (a es)) => SomeStruct a -> (forall es. (Extendss a es, PokeChain es) => Ptr (a es) -> IO b) -> IO b Source #

Write the C representation of some extended a and use the pointer, the pointer must not be returned from the continuation.

peekSomeCStruct :: forall a. (Extensible a, forall es. (Extendss a es, PeekChain es) => FromCStruct (a es)) => Ptr (SomeStruct a) -> IO (SomeStruct a) Source #

Given a pointer to a struct with an unknown chain, peek the struct and its chain.

pokeSomeCStruct Source #

Arguments

:: (forall es. (Extendss a es, PokeChain es) => ToCStruct (a es)) 
=> Ptr (SomeStruct a)

Pointer to some memory at least the size of the head of the struct chain.

-> SomeStruct a

The struct to poke

-> IO b

Computation to run while the poked tail is valid

-> IO b 

Given some memory for the head of the chain, allocate and poke the tail and run an action.

forgetExtensions :: Ptr (a es) -> Ptr (SomeStruct a) Source #

Forget which extensions a pointed-to struct has by casting the pointer

class Extensible (a :: [Type] -> Type) where Source #

Methods

extensibleTypeName :: String Source #

For error reporting an invalid extension

getNext :: a es -> Chain es Source #

setNext :: a ds -> Chain es -> a es Source #

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

Instances

Instances details
Extensible SystemProperties Source # 
Instance details

Defined in OpenXR.Core10.Device

Methods

extensibleTypeName :: String Source #

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

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

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

Extensible SessionCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Device

Methods

extensibleTypeName :: String Source #

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

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

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

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 #

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 #

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 #

Extensible InteractionProfileSuggestedBinding Source # 
Instance details

Defined in OpenXR.Core10.Input

Extensible InstanceCreateInfo Source # 
Instance details

Defined in OpenXR.Core10.Instance

Methods

extensibleTypeName :: String Source #

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

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

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

Extensible CompositionLayerProjectionView Source # 
Instance details

Defined in OpenXR.Core10.OtherTypes

Methods

extensibleTypeName :: String Source #

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

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

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

Extensible CompositionLayerBaseHeader Source # 
Instance details

Defined in OpenXR.Core10.OtherTypes

Methods

extensibleTypeName :: String Source #

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

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

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

Extensible SessionBeginInfo Source # 
Instance details

Defined in OpenXR.Core10.Session

Methods

extensibleTypeName :: String Source #

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

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

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

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 #

Extensible ViewConfigurationView Source # 
Instance details

Defined in OpenXR.Core10.ViewConfigurations

Methods

extensibleTypeName :: String Source #

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

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

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

Extensible HandTrackerCreateInfoEXT Source # 
Instance details

Defined in OpenXR.Extensions.XR_EXT_hand_tracking

Methods

extensibleTypeName :: String Source #

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

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

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

Extensible HandJointLocationsEXT Source # 
Instance details

Defined in OpenXR.Extensions.XR_EXT_hand_tracking

Methods

extensibleTypeName :: String Source #

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

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

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

pattern (::&) :: Extensible a => a es' -> Chain es -> a es infix 6 Source #

A pattern synonym to separate the head of a struct chain from the tail, use in conjunction with :& to extract several members.

Head{..} ::& () <- returningNoTail a b c
-- Equivalent to
Head{..} <- returningNoTail @'[] a b c
Head{..} ::& Foo{..} :& Bar{..} :& () <- returningWithTail a b c
myFun (Head{..} :&& Foo{..} :& ())

pattern (:&) :: e -> Chain es -> Chain (e ': es) infixr 7 Source #

View the head and tail of a Chain, see ::&

Equivalent to (,)

data SomeChild (a :: Type) where Source #

Constructors

SomeChild :: forall a b. (Inherits a b, Typeable b, ToCStruct b, Show b) => b -> SomeChild a 

Instances

Instances details
Show (SomeChild a) Source # 
Instance details

Defined in OpenXR.CStruct.Extends

withSomeChild :: SomeChild a -> (Ptr (SomeChild a) -> IO b) -> IO b Source #

type family Inherits (a :: Type) (b :: Type) :: Constraint where ... Source #

Equations

Inherits SwapchainImageBaseHeader SwapchainImageD3D12KHR = () 
Inherits SwapchainImageBaseHeader SwapchainImageD3D11KHR = () 
Inherits SwapchainImageBaseHeader SwapchainImageVulkanKHR = () 
Inherits SwapchainImageBaseHeader SwapchainImageOpenGLESKHR = () 
Inherits SwapchainImageBaseHeader SwapchainImageOpenGLKHR = () 
Inherits (CompositionLayerBaseHeader '[]) CompositionLayerEquirect2KHR = () 
Inherits (CompositionLayerBaseHeader '[]) CompositionLayerEquirectKHR = () 
Inherits (CompositionLayerBaseHeader '[]) CompositionLayerCubeKHR = () 
Inherits (CompositionLayerBaseHeader '[]) CompositionLayerCylinderKHR = () 
Inherits (CompositionLayerBaseHeader '[]) CompositionLayerQuad = () 
Inherits (CompositionLayerBaseHeader '[]) CompositionLayerProjection = () 
Inherits HapticBaseHeader HapticVibration = () 
Inherits EventDataBaseHeader EventDataDisplayRefreshRateChangedFB = () 
Inherits EventDataBaseHeader EventDataMainSessionVisibilityChangedEXTX = () 
Inherits EventDataBaseHeader EventDataInteractionProfileChanged = () 
Inherits EventDataBaseHeader EventDataVisibilityMaskChangedKHR = () 
Inherits EventDataBaseHeader EventDataPerfSettingsEXT = () 
Inherits EventDataBaseHeader EventDataReferenceSpaceChangePending = () 
Inherits EventDataBaseHeader EventDataSessionStateChanged = () 
Inherits EventDataBaseHeader EventDataInstanceLossPending = () 
Inherits EventDataBaseHeader EventDataEventsLost = () 
Inherits LoaderInitInfoBaseHeaderKHR LoaderInitInfoAndroidKHR = () 
Inherits parent child = TypeError ((ShowType parent :<>: Text " is not inherited by ") :<>: ShowType child)