| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
OpenXR.Extensions.XR_EXT_debug_utils
Description
Name
XR_EXT_debug_utils - instance extension
Specification
See XR_EXT_debug_utils in the main specification for complete information.
Registered Extension Number
20
Revision
3
Extension and Version Dependencies
- Requires OpenXR 1.0
See Also
PFN_xrDebugUtilsMessengerCallbackEXT, DebugUtilsLabelEXT,
DebugUtilsMessengerCallbackDataEXT,
DebugUtilsMessengerCreateInfoEXT, DebugUtilsObjectNameInfoEXT,
createDebugUtilsMessengerEXT, destroyDebugUtilsMessengerEXT,
sessionBeginDebugUtilsLabelRegionEXT,
sessionEndDebugUtilsLabelRegionEXT, sessionInsertDebugUtilsLabelEXT,
setDebugUtilsObjectNameEXT, submitDebugUtilsMessageEXT
Document Notes
For more information, see the OpenXR Specification
This page is a generated document. Fixes and changes should be made to the generator scripts, not directly.
Synopsis
- setDebugUtilsObjectNameEXT :: forall io. MonadIO io => Instance -> DebugUtilsObjectNameInfoEXT -> io ()
- createDebugUtilsMessengerEXT :: forall io. MonadIO io => Instance -> DebugUtilsMessengerCreateInfoEXT -> io DebugUtilsMessengerEXT
- withDebugUtilsMessengerEXT :: forall io r. MonadIO io => Instance -> DebugUtilsMessengerCreateInfoEXT -> (io DebugUtilsMessengerEXT -> (DebugUtilsMessengerEXT -> io ()) -> r) -> r
- destroyDebugUtilsMessengerEXT :: forall io. MonadIO io => DebugUtilsMessengerEXT -> io ()
- submitDebugUtilsMessageEXT :: forall io. MonadIO io => Instance -> DebugUtilsMessageSeverityFlagsEXT -> ("messageTypes" ::: DebugUtilsMessageTypeFlagsEXT) -> DebugUtilsMessengerCallbackDataEXT -> io ()
- sessionBeginDebugUtilsLabelRegionEXT :: forall io. MonadIO io => Session -> ("labelInfo" ::: DebugUtilsLabelEXT) -> io Result
- sessionEndDebugUtilsLabelRegionEXT :: forall io. MonadIO io => Session -> io Result
- sessionInsertDebugUtilsLabelEXT :: forall io. MonadIO io => Session -> ("labelInfo" ::: DebugUtilsLabelEXT) -> io Result
- data DebugUtilsObjectNameInfoEXT = DebugUtilsObjectNameInfoEXT {}
- data DebugUtilsLabelEXT = DebugUtilsLabelEXT {}
- data DebugUtilsMessengerCallbackDataEXT = DebugUtilsMessengerCallbackDataEXT {}
- data DebugUtilsMessengerCreateInfoEXT = DebugUtilsMessengerCreateInfoEXT {}
- newtype DebugUtilsMessageSeverityFlagsEXT = DebugUtilsMessageSeverityFlagsEXT Flags64
- newtype DebugUtilsMessageTypeFlagsEXT = DebugUtilsMessageTypeFlagsEXT Flags64
- type PFN_xrDebugUtilsMessengerCallbackEXT = FunPtr FN_xrDebugUtilsMessengerCallbackEXT
- type FN_xrDebugUtilsMessengerCallbackEXT = DebugUtilsMessageSeverityFlagsEXT -> ("messageTypes" ::: DebugUtilsMessageTypeFlagsEXT) -> Ptr DebugUtilsMessengerCallbackDataEXT -> ("userData" ::: Ptr ()) -> IO Bool32
- type EXT_debug_utils_SPEC_VERSION = 3
- pattern EXT_debug_utils_SPEC_VERSION :: forall a. Integral a => a
- type EXT_DEBUG_UTILS_EXTENSION_NAME = "XR_EXT_debug_utils"
- pattern EXT_DEBUG_UTILS_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
- data DebugUtilsMessengerEXT = DebugUtilsMessengerEXT {}
Documentation
setDebugUtilsObjectNameEXT Source #
Arguments
| :: forall io. MonadIO io | |
| => Instance |
|
| -> DebugUtilsObjectNameInfoEXT |
|
| -> io () |
xrSetDebugUtilsObjectNameEXT - Sets debug utils object name
Valid Usage
- In the structure pointed to by
nameInfo,DebugUtilsObjectNameInfoEXT::objectTypemust not beOBJECT_TYPE_UNKNOWN
- In the structure pointed to by
nameInfo,DebugUtilsObjectNameInfoEXT::objectHandlemust not be XR_NULL_HANDLE
Valid Usage (Implicit)
- The @@
extension must be enabled prior to calling
setDebugUtilsObjectNameEXT
-
instancemust be a validInstancehandle -
nameInfomust be a pointer to a validDebugUtilsObjectNameInfoEXTstructure
Thread Safety
- Access to the
objectHandlemember of thenameInfoparameter must be externally synchronized
Return Codes
Applications may change the name associated with an object simply by
calling setDebugUtilsObjectNameEXT again with a new string. If
DebugUtilsObjectNameInfoEXT::objectName is an empty string, then any
previously set name is removed.
See Also
createDebugUtilsMessengerEXT Source #
Arguments
| :: forall io. MonadIO io | |
| => Instance |
|
| -> DebugUtilsMessengerCreateInfoEXT |
|
| -> io DebugUtilsMessengerEXT |
xrCreateDebugUtilsMessengerEXT - Creates a debug messenger
Valid Usage (Implicit)
- The @@
extension must be enabled prior to calling
createDebugUtilsMessengerEXT
-
instancemust be a validInstancehandle -
createInfomust be a pointer to a validDebugUtilsMessengerCreateInfoEXTstructure -
messengermust be a pointer to anDebugUtilsMessengerEXThandle
Thread Safety
- Access to
instance, and any child handles, must be externally synchronized
Return Codes
The application must ensure that createDebugUtilsMessengerEXT is not
executed in parallel with any OpenXR function that is also called with
instance or child of instance.
When an event of interest occurs a debug messenger calls its
createInfo->userCallback with a debug message from the producer of
the event. Additionally, the debug messenger must filter out any debug
messages that the application’s callback is not interested in based on
DebugUtilsMessengerCreateInfoEXT flags, as described below.
See Also
DebugUtilsMessengerCreateInfoEXT,
DebugUtilsMessengerEXT,
Instance, destroyDebugUtilsMessengerEXT
withDebugUtilsMessengerEXT :: forall io r. MonadIO io => Instance -> DebugUtilsMessengerCreateInfoEXT -> (io DebugUtilsMessengerEXT -> (DebugUtilsMessengerEXT -> io ()) -> r) -> r Source #
A convenience wrapper to make a compatible pair of calls to
createDebugUtilsMessengerEXT and destroyDebugUtilsMessengerEXT
To ensure that destroyDebugUtilsMessengerEXT 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.
destroyDebugUtilsMessengerEXT Source #
Arguments
| :: forall io. MonadIO io | |
| => DebugUtilsMessengerEXT |
|
| -> io () |
xrDestroyDebugUtilsMessengerEXT - Destroys a debug messenger
Valid Usage (Implicit)
- The @@
extension must be enabled prior to calling
destroyDebugUtilsMessengerEXT
-
messengermust be a validDebugUtilsMessengerEXThandle
Thread Safety
- Access to
messengermust be externally synchronized
- Access to the
Instanceused to createmessenger, and all of its child handles must be externally synchronized
Return Codes
The application must ensure that destroyDebugUtilsMessengerEXT is
not executed in parallel with any OpenXR function that is also called
with the instance or child of instance that it was created with.
See Also
submitDebugUtilsMessageEXT Source #
Arguments
| :: forall io. MonadIO io | |
| => Instance |
|
| -> DebugUtilsMessageSeverityFlagsEXT |
|
| -> ("messageTypes" ::: DebugUtilsMessageTypeFlagsEXT) |
|
| -> DebugUtilsMessengerCallbackDataEXT |
|
| -> io () |
xrSubmitDebugUtilsMessageEXT - Submits debug utils message
Valid Usage
- For each structure in
objectsfound incallbackData, the value ofDebugUtilsObjectNameInfoEXT::objectTypemust not beOBJECT_TYPE_UNKNOWN
Valid Usage (Implicit)
- The @@
extension must be enabled prior to calling
submitDebugUtilsMessageEXT
-
instancemust be a validInstancehandle -
messageSeveritymust be a valid combination of XrDebugUtilsMessageSeverityFlagBitsEXT values -
messageSeveritymust not be0 -
messageTypesmust be a valid combination of XrDebugUtilsMessageTypeFlagBitsEXT values -
messageTypesmust not be0 -
callbackDatamust be a pointer to a validDebugUtilsMessengerCallbackDataEXTstructure
Return Codes
The application can also produce a debug message, and submit it into the OpenXR messaging system.
The call will propagate through the layers and generate callback(s) as indicated by the message’s flags. The parameters are passed on to the callback in addition to the userData value that was defined at the time the messenger was created.
See Also
DebugUtilsMessageSeverityFlagsEXT, DebugUtilsMessageTypeFlagsEXT,
DebugUtilsMessengerCallbackDataEXT, Instance
sessionBeginDebugUtilsLabelRegionEXT Source #
Arguments
| :: forall io. MonadIO io | |
| => Session |
|
| -> ("labelInfo" ::: DebugUtilsLabelEXT) |
|
| -> io Result |
xrSessionBeginDebugUtilsLabelRegionEXT - Session begin debug utils label region
Valid Usage (Implicit)
-
The @@ extension must be enabled prior to calling
sessionBeginDebugUtilsLabelRegionEXT
-
sessionmust be a validSessionhandle -
labelInfomust be a pointer to a validDebugUtilsLabelEXTstructure
Return Codes
The sessionBeginDebugUtilsLabelRegionEXT function begins a label
region within session.
See Also
sessionEndDebugUtilsLabelRegionEXT Source #
Arguments
| :: forall io. MonadIO io | |
| => Session |
|
| -> io Result |
xrSessionEndDebugUtilsLabelRegionEXT - Session end debug utils label region
Valid Usage
sessionEndDebugUtilsLabelRegionEXTmust be called only after a matchingsessionBeginDebugUtilsLabelRegionEXT.
Valid Usage (Implicit)
- The
@@ extension must be enabled prior to calling
sessionEndDebugUtilsLabelRegionEXT
-
sessionmust be a validSessionhandle
Return Codes
This function ends the last label region begun with the
sessionBeginDebugUtilsLabelRegionEXT function within the same
session.
See Also
sessionInsertDebugUtilsLabelEXT Source #
Arguments
| :: forall io. MonadIO io | |
| => Session |
|
| -> ("labelInfo" ::: DebugUtilsLabelEXT) |
|
| -> io Result |
xrSessionInsertDebugUtilsLabelEXT - Session insert debug utils label
Valid Usage (Implicit)
- The @@
extension must be enabled prior to calling
sessionInsertDebugUtilsLabelEXT
-
sessionmust be a validSessionhandle -
labelInfomust be a pointer to a validDebugUtilsLabelEXTstructure
Return Codes
The sessionInsertDebugUtilsLabelEXT function inserts an individual
label within session. The individual labels are useful for different
reasons based on the type of debugging scenario. When used with
something active like a profiler or debugger, it identifies a single
point of time. When used with logging, the individual label identifies
that a particular location has been passed at the point the log message
is triggered. Because of this usage, individual labels only exist in a
log until the next call to any of the label functions:
sessionBeginDebugUtilsLabelRegionEXTsessionEndDebugUtilsLabelRegionEXTsessionInsertDebugUtilsLabelEXT
See Also
DebugUtilsLabelEXT, Session,
sessionBeginDebugUtilsLabelRegionEXT,
sessionEndDebugUtilsLabelRegionEXT
data DebugUtilsObjectNameInfoEXT Source #
XrDebugUtilsObjectNameInfoEXT - Debug utils object name info
Valid Usage
- If
objectTypeisOBJECT_TYPE_UNKNOWN,objectHandlemust not be XR_NULL_HANDLE
- If
objectTypeis notOBJECT_TYPE_UNKNOWN,objectHandlemust be XR_NULL_HANDLE or an OpenXR handle of the type associated withobjectType
Valid Usage (Implicit)
- The @@
extension must be enabled prior to using
DebugUtilsObjectNameInfoEXT
-
typemust beTYPE_DEBUG_UTILS_OBJECT_NAME_INFO_EXT -
nextmust beNULLor a valid pointer to the next structure in a structure chain -
objectTypemust be a validObjectTypevalue - If
objectNameis notNULL,objectNamemust be a null-terminated UTF-8 string
See Also
DebugUtilsMessengerCallbackDataEXT,
ObjectType,
StructureType,
setDebugUtilsObjectNameEXT
Constructors
| DebugUtilsObjectNameInfoEXT | |
Fields
| |
Instances
data DebugUtilsLabelEXT Source #
XrDebugUtilsLabelEXT - Debug Utils Label
Valid Usage (Implicit)
- The @@ extension
must be enabled prior to using
DebugUtilsLabelEXT
-
typemust beTYPE_DEBUG_UTILS_LABEL_EXT -
nextmust beNULLor a valid pointer to the next structure in a structure chain -
labelNamemust be a null-terminated UTF-8 string
See Also
DebugUtilsMessengerCallbackDataEXT,
StructureType,
sessionBeginDebugUtilsLabelRegionEXT,
sessionInsertDebugUtilsLabelEXT
Constructors
| DebugUtilsLabelEXT | |
Fields
| |
Instances
| Show DebugUtilsLabelEXT Source # | |
Defined in OpenXR.Extensions.XR_EXT_debug_utils Methods showsPrec :: Int -> DebugUtilsLabelEXT -> ShowS # show :: DebugUtilsLabelEXT -> String # showList :: [DebugUtilsLabelEXT] -> ShowS # | |
| Zero DebugUtilsLabelEXT Source # | |
Defined in OpenXR.Extensions.XR_EXT_debug_utils Methods | |
| ToCStruct DebugUtilsLabelEXT Source # | |
Defined in OpenXR.Extensions.XR_EXT_debug_utils Methods withCStruct :: DebugUtilsLabelEXT -> (Ptr DebugUtilsLabelEXT -> IO b) -> IO b # pokeCStruct :: Ptr DebugUtilsLabelEXT -> DebugUtilsLabelEXT -> IO b -> IO b # withZeroCStruct :: (Ptr DebugUtilsLabelEXT -> IO b) -> IO b # pokeZeroCStruct :: Ptr DebugUtilsLabelEXT -> IO b -> IO b # cStructSize :: Int # cStructAlignment :: Int # | |
| FromCStruct DebugUtilsLabelEXT Source # | |
Defined in OpenXR.Extensions.XR_EXT_debug_utils Methods peekCStruct :: Ptr DebugUtilsLabelEXT -> IO DebugUtilsLabelEXT # | |
data DebugUtilsMessengerCallbackDataEXT Source #
XrDebugUtilsMessengerCallbackDataEXT - Debug utils messenger callback data
Valid Usage (Implicit)
- The
@@ extension must be enabled prior to using
DebugUtilsMessengerCallbackDataEXT
-
typemust beTYPE_DEBUG_UTILS_MESSENGER_CALLBACK_DATA_EXT -
nextmust beNULLor a valid pointer to the next structure in a structure chain -
messageIdmust be a null-terminated UTF-8 string -
functionNamemust be a null-terminated UTF-8 string -
messagemust be a null-terminated UTF-8 string
An DebugUtilsMessengerCallbackDataEXT is a messenger object that
handles passing along debug messages to a provided debug callback.
Note
This structure should only be considered valid during the lifetime of the triggered callback.
The labels listed inside sessionLabels are organized in time order,
with the most recently generated label appearing first, and the oldest
label appearing last.
See Also
DebugUtilsLabelEXT, DebugUtilsObjectNameInfoEXT,
StructureType,
submitDebugUtilsMessageEXT
Constructors
| DebugUtilsMessengerCallbackDataEXT | |
Fields
| |
Instances
| Show DebugUtilsMessengerCallbackDataEXT Source # | |
Defined in OpenXR.Extensions.XR_EXT_debug_utils Methods showsPrec :: Int -> DebugUtilsMessengerCallbackDataEXT -> ShowS # | |
| Zero DebugUtilsMessengerCallbackDataEXT Source # | |
Defined in OpenXR.Extensions.XR_EXT_debug_utils Methods | |
| ToCStruct DebugUtilsMessengerCallbackDataEXT Source # | |
Defined in OpenXR.Extensions.XR_EXT_debug_utils Methods withCStruct :: DebugUtilsMessengerCallbackDataEXT -> (Ptr DebugUtilsMessengerCallbackDataEXT -> IO b) -> IO b # pokeCStruct :: Ptr DebugUtilsMessengerCallbackDataEXT -> DebugUtilsMessengerCallbackDataEXT -> IO b -> IO b # withZeroCStruct :: (Ptr DebugUtilsMessengerCallbackDataEXT -> IO b) -> IO b # pokeZeroCStruct :: Ptr DebugUtilsMessengerCallbackDataEXT -> IO b -> IO b # cStructSize :: Int # cStructAlignment :: Int # | |
| FromCStruct DebugUtilsMessengerCallbackDataEXT Source # | |
data DebugUtilsMessengerCreateInfoEXT Source #
XrDebugUtilsMessengerCreateInfoEXT - Debug utils messenger create info
Valid Usage
userCallbackmust be a valid PFN_xrDebugUtilsMessengerCallbackEXT
Valid Usage (Implicit)
- The
@@ extension must be enabled prior to using
DebugUtilsMessengerCreateInfoEXT
-
typemust beTYPE_DEBUG_UTILS_MESSENGER_CREATE_INFO_EXT -
nextmust beNULLor a valid pointer to the next structure in a structure chain -
messageSeveritiesmust be a valid combination of XrDebugUtilsMessageSeverityFlagBitsEXT values -
messageSeveritiesmust not be0 -
messageTypesmust be a valid combination of XrDebugUtilsMessageTypeFlagBitsEXT values -
messageTypesmust not be0 -
userCallbackmust be a validPFN_xrDebugUtilsMessengerCallbackEXTvalue
For each DebugUtilsMessengerEXT that is
created the DebugUtilsMessengerCreateInfoEXT::messageSeverities and
DebugUtilsMessengerCreateInfoEXT::messageTypes determine when that
DebugUtilsMessengerCreateInfoEXT::userCallback is called. The
process to determine if the user’s userCallback is triggered when an
event occurs is as follows:
- The runtime will perform a bitwise AND of the event’s
XrDebugUtilsMessageSeverityFlagBitsEXT
with the
DebugUtilsMessengerCreateInfoEXT::messageSeveritiesprovided during creation of theDebugUtilsMessengerEXTobject. - If this results in
0, the message is skipped. - The runtime will perform bitwise AND of the event’s
XrDebugUtilsMessageTypeFlagBitsEXT
with the
DebugUtilsMessengerCreateInfoEXT::messageTypesprovided during the creation of theDebugUtilsMessengerEXTobject. - If this results in
0, the message is skipped. - If the message of the current event is not skipped, the callback will be called with the message.
The callback will come directly from the component that detected the event, unless some other layer intercepts the calls for its own purposes (filter them in a different way, log to a system error log, etc.).
See Also
PFN_xrDebugUtilsMessengerCallbackEXT,
DebugUtilsMessageSeverityFlagsEXT, DebugUtilsMessageTypeFlagsEXT,
StructureType,
createDebugUtilsMessengerEXT
Constructors
| DebugUtilsMessengerCreateInfoEXT | |
Fields
| |
Instances
newtype DebugUtilsMessageSeverityFlagsEXT Source #
XrDebugUtilsMessageSeverityFlagsEXT - XrDebugUtilsMessageSeverityFlagsEXT
See Also
DebugUtilsMessengerCreateInfoEXT, submitDebugUtilsMessageEXT
Constructors
| DebugUtilsMessageSeverityFlagsEXT Flags64 |
Instances
newtype DebugUtilsMessageTypeFlagsEXT Source #
XrDebugUtilsMessageTypeFlagsEXT - XrDebugUtilsMessageTypeFlagsEXT
See Also
DebugUtilsMessengerCreateInfoEXT, submitDebugUtilsMessageEXT
Constructors
| DebugUtilsMessageTypeFlagsEXT Flags64 |
Instances
type PFN_xrDebugUtilsMessengerCallbackEXT = FunPtr FN_xrDebugUtilsMessengerCallbackEXT Source #
PFN_xrDebugUtilsMessengerCallbackEXT - Type of callback function invoked by the debug utils
Parameter Descriptions
Description
The callback must not call destroyDebugUtilsMessengerEXT.
The callback returns an
https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrBool32
that indicates to the calling layer the application’s desire to abort
the call. A value of TRUE indicates
that the application wants to abort this call. If the application
returns FALSE, the function must not
be aborted. Applications should always return
FALSE so that they see the same
behavior with and without validation layers enabled.
If the application returns TRUE from
its callback and the OpenXR call being aborted returns an
Result, the layer will return
ERROR_VALIDATION_FAILURE.
The object pointed to by callbackData (and any pointers in it
recursively) must be valid during the lifetime of the triggered
callback. It may become invalid afterwards.
See Also
DebugUtilsMessengerCreateInfoEXT, createDebugUtilsMessengerEXT
type FN_xrDebugUtilsMessengerCallbackEXT = DebugUtilsMessageSeverityFlagsEXT -> ("messageTypes" ::: DebugUtilsMessageTypeFlagsEXT) -> Ptr DebugUtilsMessengerCallbackDataEXT -> ("userData" ::: Ptr ()) -> IO Bool32 Source #
type EXT_debug_utils_SPEC_VERSION = 3 Source #
pattern EXT_debug_utils_SPEC_VERSION :: forall a. Integral a => a Source #
type EXT_DEBUG_UTILS_EXTENSION_NAME = "XR_EXT_debug_utils" Source #
pattern EXT_DEBUG_UTILS_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a Source #
data DebugUtilsMessengerEXT Source #
XrDebugUtilsMessengerEXT - Callback for debug data
Description
DebugUtilsMessengerEXT represents a callback function and associated
filters registered with the runtime.
See Also
Constructors
| DebugUtilsMessengerEXT | |
Instances
| Eq DebugUtilsMessengerEXT Source # | |
Defined in OpenXR.Extensions.Handles Methods (==) :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool # (/=) :: DebugUtilsMessengerEXT -> DebugUtilsMessengerEXT -> Bool # | |
| Show DebugUtilsMessengerEXT Source # | |
Defined in OpenXR.Extensions.Handles Methods showsPrec :: Int -> DebugUtilsMessengerEXT -> ShowS # show :: DebugUtilsMessengerEXT -> String # showList :: [DebugUtilsMessengerEXT] -> ShowS # | |
| Zero DebugUtilsMessengerEXT Source # | |
Defined in OpenXR.Extensions.Handles Methods | |
| HasObjectType DebugUtilsMessengerEXT Source # | |
Defined in OpenXR.Extensions.Handles Methods objectTypeAndHandle :: DebugUtilsMessengerEXT -> (ObjectType, Word64) Source # | |
| IsHandle DebugUtilsMessengerEXT Source # | |
Defined in OpenXR.Extensions.Handles | |