{-# language CPP #-}
-- No documentation found for Chapter "SessionState"
module OpenXR.Core10.Enums.SessionState  (SessionState( SESSION_STATE_UNKNOWN
                                                      , SESSION_STATE_IDLE
                                                      , SESSION_STATE_READY
                                                      , SESSION_STATE_SYNCHRONIZED
                                                      , SESSION_STATE_VISIBLE
                                                      , SESSION_STATE_FOCUSED
                                                      , SESSION_STATE_STOPPING
                                                      , SESSION_STATE_LOSS_PENDING
                                                      , SESSION_STATE_EXITING
                                                      , ..
                                                      )) where

import OpenXR.Internal.Utils (enumReadPrec)
import OpenXR.Internal.Utils (enumShowsPrec)
import GHC.Show (showsPrec)
import OpenXR.Zero (Zero)
import Foreign.Storable (Storable)
import Data.Int (Int32)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))

-- | XrSessionState - Session lifecycle state
--
-- == Enumerant Descriptions
--
-- The 'SESSION_STATE_UNKNOWN' state /must/ not be returned by the runtime,
-- and is only defined to avoid @0@ being a valid state.
--
-- Receiving the 'SESSION_STATE_IDLE' state indicates that the runtime
-- considers the session is idle. Applications in this state /should/
-- minimize resource consumption but continue to call
-- 'OpenXR.Core10.Instance.pollEvent' at some reasonable cadence.
--
-- Receiving the 'SESSION_STATE_READY' state indicates that the runtime
-- desires the application to prepare rendering resources, begin its
-- session and synchronize its frame loop with the runtime.
-- #sync_frame_loop# The application does this by successfully calling
-- 'OpenXR.Core10.Session.beginSession' and then running its frame loop by
-- calling 'OpenXR.Core10.DisplayTiming.waitFrame',
-- 'OpenXR.Core10.DisplayTiming.beginFrame' and
-- 'OpenXR.Core10.DisplayTiming.endFrame' in a loop. If the runtime wishes
-- to return the session to the 'SESSION_STATE_IDLE' state, it /must/ wait
-- until the application calls 'OpenXR.Core10.Session.beginSession'. After
-- returning from the 'OpenXR.Core10.Session.beginSession' call, the
-- runtime may then immediately transition forward through the
-- 'SESSION_STATE_SYNCHRONIZED' state to the 'SESSION_STATE_STOPPING'
-- state, to request that the application end this session. If the system
-- supports a user engagement sensor and runtime is in 'SESSION_STATE_IDLE'
-- state, the runtime /should/ not transition to the 'SESSION_STATE_READY'
-- state until the user starts engaging with the device.
--
-- Receiving the 'SESSION_STATE_SYNCHRONIZED' state indicates that the
-- application has
-- <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#sync_frame_loop synchronized its frame loop with the runtime>,
-- but its frames are not visible to the user. The application /should/
-- continue running its frame loop by calling
-- 'OpenXR.Core10.DisplayTiming.waitFrame',
-- 'OpenXR.Core10.DisplayTiming.beginFrame' and
-- 'OpenXR.Core10.DisplayTiming.endFrame', although it should avoid heavy
-- GPU work so that other visible applications can take CPU and GPU
-- precedence. The application can save resources here by skipping
-- rendering and not submitting any composition layers until
-- 'OpenXR.Core10.DisplayTiming.waitFrame' returns an
-- 'OpenXR.Core10.DisplayTiming.FrameState' with @shouldRender@ set to
-- true. A runtime /may/ use this frame synchronization to facilitate
-- seamless switching from a previous XR application to this application on
-- a frame boundary.
--
-- Receiving the 'SESSION_STATE_VISIBLE' state indicates that the
-- application has
-- <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#sync_frame_loop synchronized its frame loop with the runtime>,
-- and the session’s frames will be visible to the user, but the session is
-- not eligible to receive XR input. An application may be visible but not
-- have focus, for example when the runtime is composing a modal pop-up on
-- top of the application’s rendered frames. The application /should/
-- continue running its frame loop, rendering and submitting its
-- composition layers, although it may wish to pause its experience, as
-- users cannot interact with the application at this time. It is important
-- for applications to continue rendering when visible, even when they do
-- not have focus, so the user continues to see something reasonable
-- underneath modal pop-ups. Runtimes /should/ make input actions inactive
-- while the application is unfocused, and applications should react to an
-- inactive input action by skipping rendering of that action’s input
-- avatar (depictions of hands or other tracked objects controlled by the
-- user).
--
-- Receiving the 'SESSION_STATE_FOCUSED' state indicates that the
-- application has
-- <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#sync_frame_loop synchronized its frame loop with the runtime>,
-- the session’s frames will be visible to the user, and the session is
-- eligible to receive XR input. The runtime /should/ only give one session
-- XR input focus at any given time. The application /should/ be running
-- its frame loop, rendering and submitting composition layers, including
-- input avatars (depictions of hands or other tracked objects controlled
-- by the user) for any input actions that are active. The runtime /should/
-- avoid rendering its own input avatars when an application is focused,
-- unless input from a given source is being captured by the runtime at the
-- moment.
--
-- Receiving the 'SESSION_STATE_STOPPING' state indicates that the runtime
-- has determined that the application should halt its rendering loop.
-- Applications /should/ exit their rendering loop and call
-- 'OpenXR.Core10.Session.endSession' when in this state. A possible reason
-- for this would be to minimize contention between multiple applications.
-- If the system supports a user engagement sensor and the session is
-- running, the runtime /should/ transition to the 'SESSION_STATE_STOPPING'
-- state when the user stops engaging with the device.
--
-- Receiving the 'SESSION_STATE_EXITING' state indicates the runtime wishes
-- the application to terminate its XR experience, typically due to a user
-- request via a runtime user interface. Applications /should/ gracefully
-- end their process when in this state if they do not have a non-XR user
-- experience.
--
-- Receiving the 'SESSION_STATE_LOSS_PENDING' state indicates the runtime
-- is no longer able to operate with the current session, for example due
-- to the loss of a display hardware connection. An application /should/
-- call 'OpenXR.Core10.Device.destroySession' and /may/ end its process or
-- decide to poll 'OpenXR.Core10.Device.getSystem' at some reasonable
-- cadence to get a new
-- <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#XrSystemId >,
-- and re-initialize all graphics resources related to the new system, and
-- then create a new session using 'OpenXR.Core10.Device.createSession'.
-- After the event is queued, subsequent calls to functions that accept
-- 'OpenXR.Core10.Handles.Session' parameters /must/ no longer return any
-- success code other than
-- 'OpenXR.Core10.Enums.Result.SESSION_LOSS_PENDING' for the given
-- 'OpenXR.Core10.Handles.Session' handle. The
-- 'OpenXR.Core10.Enums.Result.SESSION_LOSS_PENDING' success result is
-- returned for an unspecified grace period of time, and the functions that
-- return it simulate success in their behavior. If the runtime has no
-- reasonable way to successfully complete a given function (e.g.
-- 'OpenXR.Core10.Image.createSwapchain') when a lost session is pending,
-- or if the runtime is not able to provide the application a grace period,
-- the runtime /may/ return
-- 'OpenXR.Core10.Enums.Result.ERROR_SESSION_LOST'. Thereafter, functions
-- which accept 'OpenXR.Core10.Handles.Session' parameters for the lost
-- session /may/ return 'OpenXR.Core10.Enums.Result.ERROR_SESSION_LOST' to
-- indicate that the function failed and the given session was lost. The
-- 'OpenXR.Core10.Handles.Session' handle and child handles are henceforth
-- unusable and /should/ be destroyed by the application in order to
-- immediately free up resources associated with those handles.
--
-- = See Also
--
-- 'OpenXR.Core10.OtherTypes.EventDataSessionStateChanged',
-- 'OpenXR.Core10.Instance.pollEvent'
newtype SessionState = SessionState Int32
  deriving newtype (SessionState -> SessionState -> Bool
(SessionState -> SessionState -> Bool)
-> (SessionState -> SessionState -> Bool) -> Eq SessionState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SessionState -> SessionState -> Bool
$c/= :: SessionState -> SessionState -> Bool
== :: SessionState -> SessionState -> Bool
$c== :: SessionState -> SessionState -> Bool
Eq, Eq SessionState
Eq SessionState =>
(SessionState -> SessionState -> Ordering)
-> (SessionState -> SessionState -> Bool)
-> (SessionState -> SessionState -> Bool)
-> (SessionState -> SessionState -> Bool)
-> (SessionState -> SessionState -> Bool)
-> (SessionState -> SessionState -> SessionState)
-> (SessionState -> SessionState -> SessionState)
-> Ord SessionState
SessionState -> SessionState -> Bool
SessionState -> SessionState -> Ordering
SessionState -> SessionState -> SessionState
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SessionState -> SessionState -> SessionState
$cmin :: SessionState -> SessionState -> SessionState
max :: SessionState -> SessionState -> SessionState
$cmax :: SessionState -> SessionState -> SessionState
>= :: SessionState -> SessionState -> Bool
$c>= :: SessionState -> SessionState -> Bool
> :: SessionState -> SessionState -> Bool
$c> :: SessionState -> SessionState -> Bool
<= :: SessionState -> SessionState -> Bool
$c<= :: SessionState -> SessionState -> Bool
< :: SessionState -> SessionState -> Bool
$c< :: SessionState -> SessionState -> Bool
compare :: SessionState -> SessionState -> Ordering
$ccompare :: SessionState -> SessionState -> Ordering
$cp1Ord :: Eq SessionState
Ord, Ptr b -> Int -> IO SessionState
Ptr b -> Int -> SessionState -> IO ()
Ptr SessionState -> IO SessionState
Ptr SessionState -> Int -> IO SessionState
Ptr SessionState -> Int -> SessionState -> IO ()
Ptr SessionState -> SessionState -> IO ()
SessionState -> Int
(SessionState -> Int)
-> (SessionState -> Int)
-> (Ptr SessionState -> Int -> IO SessionState)
-> (Ptr SessionState -> Int -> SessionState -> IO ())
-> (forall b. Ptr b -> Int -> IO SessionState)
-> (forall b. Ptr b -> Int -> SessionState -> IO ())
-> (Ptr SessionState -> IO SessionState)
-> (Ptr SessionState -> SessionState -> IO ())
-> Storable SessionState
forall b. Ptr b -> Int -> IO SessionState
forall b. Ptr b -> Int -> SessionState -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr SessionState -> SessionState -> IO ()
$cpoke :: Ptr SessionState -> SessionState -> IO ()
peek :: Ptr SessionState -> IO SessionState
$cpeek :: Ptr SessionState -> IO SessionState
pokeByteOff :: Ptr b -> Int -> SessionState -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SessionState -> IO ()
peekByteOff :: Ptr b -> Int -> IO SessionState
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SessionState
pokeElemOff :: Ptr SessionState -> Int -> SessionState -> IO ()
$cpokeElemOff :: Ptr SessionState -> Int -> SessionState -> IO ()
peekElemOff :: Ptr SessionState -> Int -> IO SessionState
$cpeekElemOff :: Ptr SessionState -> Int -> IO SessionState
alignment :: SessionState -> Int
$calignment :: SessionState -> Int
sizeOf :: SessionState -> Int
$csizeOf :: SessionState -> Int
Storable, SessionState
SessionState -> Zero SessionState
forall a. a -> Zero a
zero :: SessionState
$czero :: SessionState
Zero)

-- | 'SESSION_STATE_UNKNOWN'. An unknown state. The runtime /must/ not return
-- this value in an 'OpenXR.Core10.OtherTypes.EventDataSessionStateChanged'
-- event.
pattern $bSESSION_STATE_UNKNOWN :: SessionState
$mSESSION_STATE_UNKNOWN :: forall r. SessionState -> (Void# -> r) -> (Void# -> r) -> r
SESSION_STATE_UNKNOWN      = SessionState 0
-- | 'SESSION_STATE_IDLE'. The initial state after calling
-- 'OpenXR.Core10.Device.createSession' or returned to after calling
-- 'OpenXR.Core10.Session.endSession'.
pattern $bSESSION_STATE_IDLE :: SessionState
$mSESSION_STATE_IDLE :: forall r. SessionState -> (Void# -> r) -> (Void# -> r) -> r
SESSION_STATE_IDLE         = SessionState 1
-- | 'SESSION_STATE_READY'. The application is ready to call
-- 'OpenXR.Core10.Session.beginSession' and
-- <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#sync_frame_loop sync its frame loop with the runtime.>
pattern $bSESSION_STATE_READY :: SessionState
$mSESSION_STATE_READY :: forall r. SessionState -> (Void# -> r) -> (Void# -> r) -> r
SESSION_STATE_READY        = SessionState 2
-- | 'SESSION_STATE_SYNCHRONIZED'. The application has synced its frame loop
-- with the runtime but is not visible to the user.
pattern $bSESSION_STATE_SYNCHRONIZED :: SessionState
$mSESSION_STATE_SYNCHRONIZED :: forall r. SessionState -> (Void# -> r) -> (Void# -> r) -> r
SESSION_STATE_SYNCHRONIZED = SessionState 3
-- | 'SESSION_STATE_VISIBLE'. The application has
-- <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#sync_frame_loop synced its frame loop with the runtime>
-- and is visible to the user but cannot receive XR input.
pattern $bSESSION_STATE_VISIBLE :: SessionState
$mSESSION_STATE_VISIBLE :: forall r. SessionState -> (Void# -> r) -> (Void# -> r) -> r
SESSION_STATE_VISIBLE      = SessionState 4
-- | 'SESSION_STATE_FOCUSED'. The application has
-- <https://www.khronos.org/registry/OpenXR/specs/1.0/html/xrspec.html#sync_frame_loop synced its frame loop with the runtime>,
-- is visible to the user and can receive XR input.
pattern $bSESSION_STATE_FOCUSED :: SessionState
$mSESSION_STATE_FOCUSED :: forall r. SessionState -> (Void# -> r) -> (Void# -> r) -> r
SESSION_STATE_FOCUSED      = SessionState 5
-- | 'SESSION_STATE_STOPPING'. The application should exit its frame loop and
-- call 'OpenXR.Core10.Session.endSession'.
pattern $bSESSION_STATE_STOPPING :: SessionState
$mSESSION_STATE_STOPPING :: forall r. SessionState -> (Void# -> r) -> (Void# -> r) -> r
SESSION_STATE_STOPPING     = SessionState 6
-- | 'SESSION_STATE_LOSS_PENDING'. The session is in the process of being
-- lost. The application should destroy the current session and can
-- optionally recreate it.
pattern $bSESSION_STATE_LOSS_PENDING :: SessionState
$mSESSION_STATE_LOSS_PENDING :: forall r. SessionState -> (Void# -> r) -> (Void# -> r) -> r
SESSION_STATE_LOSS_PENDING = SessionState 7
-- | 'SESSION_STATE_EXITING'. The application should end its XR experience
-- and not automatically restart it.
pattern $bSESSION_STATE_EXITING :: SessionState
$mSESSION_STATE_EXITING :: forall r. SessionState -> (Void# -> r) -> (Void# -> r) -> r
SESSION_STATE_EXITING      = SessionState 8
{-# complete SESSION_STATE_UNKNOWN,
             SESSION_STATE_IDLE,
             SESSION_STATE_READY,
             SESSION_STATE_SYNCHRONIZED,
             SESSION_STATE_VISIBLE,
             SESSION_STATE_FOCUSED,
             SESSION_STATE_STOPPING,
             SESSION_STATE_LOSS_PENDING,
             SESSION_STATE_EXITING :: SessionState #-}

conNameSessionState :: String
conNameSessionState :: String
conNameSessionState = "SessionState"

enumPrefixSessionState :: String
enumPrefixSessionState :: String
enumPrefixSessionState = "SESSION_STATE_"

showTableSessionState :: [(SessionState, String)]
showTableSessionState :: [(SessionState, String)]
showTableSessionState =
  [ (SessionState
SESSION_STATE_UNKNOWN     , "UNKNOWN")
  , (SessionState
SESSION_STATE_IDLE        , "IDLE")
  , (SessionState
SESSION_STATE_READY       , "READY")
  , (SessionState
SESSION_STATE_SYNCHRONIZED, "SYNCHRONIZED")
  , (SessionState
SESSION_STATE_VISIBLE     , "VISIBLE")
  , (SessionState
SESSION_STATE_FOCUSED     , "FOCUSED")
  , (SessionState
SESSION_STATE_STOPPING    , "STOPPING")
  , (SessionState
SESSION_STATE_LOSS_PENDING, "LOSS_PENDING")
  , (SessionState
SESSION_STATE_EXITING     , "EXITING")
  ]

instance Show SessionState where
  showsPrec :: Int -> SessionState -> ShowS
showsPrec = String
-> [(SessionState, String)]
-> String
-> (SessionState -> Int32)
-> (Int32 -> ShowS)
-> Int
-> SessionState
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixSessionState
                            [(SessionState, String)]
showTableSessionState
                            String
conNameSessionState
                            (\(SessionState x :: Int32
x) -> Int32
x)
                            (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11)

instance Read SessionState where
  readPrec :: ReadPrec SessionState
readPrec = String
-> [(SessionState, String)]
-> String
-> (Int32 -> SessionState)
-> ReadPrec SessionState
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixSessionState [(SessionState, String)]
showTableSessionState String
conNameSessionState Int32 -> SessionState
SessionState