{-# language CPP #-}
-- No documentation found for Chapter "SessionCreateFlags"
module OpenXR.Core10.Enums.SessionCreateFlags  (SessionCreateFlags(..)) where

import OpenXR.Internal.Utils (enumReadPrec)
import OpenXR.Internal.Utils (enumShowsPrec)
import GHC.Show (showString)
import Numeric (showHex)
import OpenXR.Zero (Zero)
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import OpenXR.Core10.FundamentalTypes (Flags64)
-- | XrSessionCreateFlags - Session Creation Flags
--
-- = Description
--
-- There are currently no session creation flags. This is reserved for
-- future use.
--
-- = See Also
--
-- 'OpenXR.Core10.Device.SessionCreateInfo',
-- 'OpenXR.Core10.Device.createSession'
newtype SessionCreateFlags = SessionCreateFlags Flags64
  deriving newtype (SessionCreateFlags -> SessionCreateFlags -> Bool
(SessionCreateFlags -> SessionCreateFlags -> Bool)
-> (SessionCreateFlags -> SessionCreateFlags -> Bool)
-> Eq SessionCreateFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SessionCreateFlags -> SessionCreateFlags -> Bool
$c/= :: SessionCreateFlags -> SessionCreateFlags -> Bool
== :: SessionCreateFlags -> SessionCreateFlags -> Bool
$c== :: SessionCreateFlags -> SessionCreateFlags -> Bool
Eq, Eq SessionCreateFlags
Eq SessionCreateFlags =>
(SessionCreateFlags -> SessionCreateFlags -> Ordering)
-> (SessionCreateFlags -> SessionCreateFlags -> Bool)
-> (SessionCreateFlags -> SessionCreateFlags -> Bool)
-> (SessionCreateFlags -> SessionCreateFlags -> Bool)
-> (SessionCreateFlags -> SessionCreateFlags -> Bool)
-> (SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags)
-> (SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags)
-> Ord SessionCreateFlags
SessionCreateFlags -> SessionCreateFlags -> Bool
SessionCreateFlags -> SessionCreateFlags -> Ordering
SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
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 :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
$cmin :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
max :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
$cmax :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
>= :: SessionCreateFlags -> SessionCreateFlags -> Bool
$c>= :: SessionCreateFlags -> SessionCreateFlags -> Bool
> :: SessionCreateFlags -> SessionCreateFlags -> Bool
$c> :: SessionCreateFlags -> SessionCreateFlags -> Bool
<= :: SessionCreateFlags -> SessionCreateFlags -> Bool
$c<= :: SessionCreateFlags -> SessionCreateFlags -> Bool
< :: SessionCreateFlags -> SessionCreateFlags -> Bool
$c< :: SessionCreateFlags -> SessionCreateFlags -> Bool
compare :: SessionCreateFlags -> SessionCreateFlags -> Ordering
$ccompare :: SessionCreateFlags -> SessionCreateFlags -> Ordering
$cp1Ord :: Eq SessionCreateFlags
Ord, Ptr b -> Int -> IO SessionCreateFlags
Ptr b -> Int -> SessionCreateFlags -> IO ()
Ptr SessionCreateFlags -> IO SessionCreateFlags
Ptr SessionCreateFlags -> Int -> IO SessionCreateFlags
Ptr SessionCreateFlags -> Int -> SessionCreateFlags -> IO ()
Ptr SessionCreateFlags -> SessionCreateFlags -> IO ()
SessionCreateFlags -> Int
(SessionCreateFlags -> Int)
-> (SessionCreateFlags -> Int)
-> (Ptr SessionCreateFlags -> Int -> IO SessionCreateFlags)
-> (Ptr SessionCreateFlags -> Int -> SessionCreateFlags -> IO ())
-> (forall b. Ptr b -> Int -> IO SessionCreateFlags)
-> (forall b. Ptr b -> Int -> SessionCreateFlags -> IO ())
-> (Ptr SessionCreateFlags -> IO SessionCreateFlags)
-> (Ptr SessionCreateFlags -> SessionCreateFlags -> IO ())
-> Storable SessionCreateFlags
forall b. Ptr b -> Int -> IO SessionCreateFlags
forall b. Ptr b -> Int -> SessionCreateFlags -> 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 SessionCreateFlags -> SessionCreateFlags -> IO ()
$cpoke :: Ptr SessionCreateFlags -> SessionCreateFlags -> IO ()
peek :: Ptr SessionCreateFlags -> IO SessionCreateFlags
$cpeek :: Ptr SessionCreateFlags -> IO SessionCreateFlags
pokeByteOff :: Ptr b -> Int -> SessionCreateFlags -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SessionCreateFlags -> IO ()
peekByteOff :: Ptr b -> Int -> IO SessionCreateFlags
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SessionCreateFlags
pokeElemOff :: Ptr SessionCreateFlags -> Int -> SessionCreateFlags -> IO ()
$cpokeElemOff :: Ptr SessionCreateFlags -> Int -> SessionCreateFlags -> IO ()
peekElemOff :: Ptr SessionCreateFlags -> Int -> IO SessionCreateFlags
$cpeekElemOff :: Ptr SessionCreateFlags -> Int -> IO SessionCreateFlags
alignment :: SessionCreateFlags -> Int
$calignment :: SessionCreateFlags -> Int
sizeOf :: SessionCreateFlags -> Int
$csizeOf :: SessionCreateFlags -> Int
Storable, SessionCreateFlags
SessionCreateFlags -> Zero SessionCreateFlags
forall a. a -> Zero a
zero :: SessionCreateFlags
$czero :: SessionCreateFlags
Zero, Eq SessionCreateFlags
SessionCreateFlags
Eq SessionCreateFlags =>
(SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags)
-> (SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags)
-> (SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags)
-> (SessionCreateFlags -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> SessionCreateFlags
-> (Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> Bool)
-> (SessionCreateFlags -> Maybe Int)
-> (SessionCreateFlags -> Int)
-> (SessionCreateFlags -> Bool)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int -> SessionCreateFlags)
-> (SessionCreateFlags -> Int)
-> Bits SessionCreateFlags
Int -> SessionCreateFlags
SessionCreateFlags -> Bool
SessionCreateFlags -> Int
SessionCreateFlags -> Maybe Int
SessionCreateFlags -> SessionCreateFlags
SessionCreateFlags -> Int -> Bool
SessionCreateFlags -> Int -> SessionCreateFlags
SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: SessionCreateFlags -> Int
$cpopCount :: SessionCreateFlags -> Int
rotateR :: SessionCreateFlags -> Int -> SessionCreateFlags
$crotateR :: SessionCreateFlags -> Int -> SessionCreateFlags
rotateL :: SessionCreateFlags -> Int -> SessionCreateFlags
$crotateL :: SessionCreateFlags -> Int -> SessionCreateFlags
unsafeShiftR :: SessionCreateFlags -> Int -> SessionCreateFlags
$cunsafeShiftR :: SessionCreateFlags -> Int -> SessionCreateFlags
shiftR :: SessionCreateFlags -> Int -> SessionCreateFlags
$cshiftR :: SessionCreateFlags -> Int -> SessionCreateFlags
unsafeShiftL :: SessionCreateFlags -> Int -> SessionCreateFlags
$cunsafeShiftL :: SessionCreateFlags -> Int -> SessionCreateFlags
shiftL :: SessionCreateFlags -> Int -> SessionCreateFlags
$cshiftL :: SessionCreateFlags -> Int -> SessionCreateFlags
isSigned :: SessionCreateFlags -> Bool
$cisSigned :: SessionCreateFlags -> Bool
bitSize :: SessionCreateFlags -> Int
$cbitSize :: SessionCreateFlags -> Int
bitSizeMaybe :: SessionCreateFlags -> Maybe Int
$cbitSizeMaybe :: SessionCreateFlags -> Maybe Int
testBit :: SessionCreateFlags -> Int -> Bool
$ctestBit :: SessionCreateFlags -> Int -> Bool
complementBit :: SessionCreateFlags -> Int -> SessionCreateFlags
$ccomplementBit :: SessionCreateFlags -> Int -> SessionCreateFlags
clearBit :: SessionCreateFlags -> Int -> SessionCreateFlags
$cclearBit :: SessionCreateFlags -> Int -> SessionCreateFlags
setBit :: SessionCreateFlags -> Int -> SessionCreateFlags
$csetBit :: SessionCreateFlags -> Int -> SessionCreateFlags
bit :: Int -> SessionCreateFlags
$cbit :: Int -> SessionCreateFlags
zeroBits :: SessionCreateFlags
$czeroBits :: SessionCreateFlags
rotate :: SessionCreateFlags -> Int -> SessionCreateFlags
$crotate :: SessionCreateFlags -> Int -> SessionCreateFlags
shift :: SessionCreateFlags -> Int -> SessionCreateFlags
$cshift :: SessionCreateFlags -> Int -> SessionCreateFlags
complement :: SessionCreateFlags -> SessionCreateFlags
$ccomplement :: SessionCreateFlags -> SessionCreateFlags
xor :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
$cxor :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
.|. :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
$c.|. :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
.&. :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
$c.&. :: SessionCreateFlags -> SessionCreateFlags -> SessionCreateFlags
$cp1Bits :: Eq SessionCreateFlags
Bits, Bits SessionCreateFlags
Bits SessionCreateFlags =>
(SessionCreateFlags -> Int)
-> (SessionCreateFlags -> Int)
-> (SessionCreateFlags -> Int)
-> FiniteBits SessionCreateFlags
SessionCreateFlags -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: SessionCreateFlags -> Int
$ccountTrailingZeros :: SessionCreateFlags -> Int
countLeadingZeros :: SessionCreateFlags -> Int
$ccountLeadingZeros :: SessionCreateFlags -> Int
finiteBitSize :: SessionCreateFlags -> Int
$cfiniteBitSize :: SessionCreateFlags -> Int
$cp1FiniteBits :: Bits SessionCreateFlags
FiniteBits)



conNameSessionCreateFlags :: String
conNameSessionCreateFlags :: String
conNameSessionCreateFlags = "SessionCreateFlags"

enumPrefixSessionCreateFlags :: String
enumPrefixSessionCreateFlags :: String
enumPrefixSessionCreateFlags = ""

showTableSessionCreateFlags :: [(SessionCreateFlags, String)]
showTableSessionCreateFlags :: [(SessionCreateFlags, String)]
showTableSessionCreateFlags = []

instance Show SessionCreateFlags where
  showsPrec :: Int -> SessionCreateFlags -> ShowS
showsPrec = String
-> [(SessionCreateFlags, String)]
-> String
-> (SessionCreateFlags -> Flags64)
-> (Flags64 -> ShowS)
-> Int
-> SessionCreateFlags
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixSessionCreateFlags
                            [(SessionCreateFlags, String)]
showTableSessionCreateFlags
                            String
conNameSessionCreateFlags
                            (\(SessionCreateFlags x :: Flags64
x) -> Flags64
x)
                            (\x :: Flags64
x -> String -> ShowS
showString "0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags64 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags64
x)

instance Read SessionCreateFlags where
  readPrec :: ReadPrec SessionCreateFlags
readPrec =
    String
-> [(SessionCreateFlags, String)]
-> String
-> (Flags64 -> SessionCreateFlags)
-> ReadPrec SessionCreateFlags
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixSessionCreateFlags [(SessionCreateFlags, String)]
showTableSessionCreateFlags String
conNameSessionCreateFlags Flags64 -> SessionCreateFlags
SessionCreateFlags