{-# language CPP #-}
module Vulkan.Core10.Enums.SemaphoreCreateFlags  (SemaphoreCreateFlags(..)) where
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.Bits (Bits)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Zero (Zero)
newtype SemaphoreCreateFlags = SemaphoreCreateFlags Flags
  deriving newtype (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
(SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> Eq SemaphoreCreateFlags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c/= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
== :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c== :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
Eq, Eq SemaphoreCreateFlags
Eq SemaphoreCreateFlags =>
(SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags
    -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags
    -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> Ord SemaphoreCreateFlags
SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering
SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
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 :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$cmin :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
max :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$cmax :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
>= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c>= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
> :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c> :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
<= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c<= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
< :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c< :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
compare :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering
$ccompare :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering
$cp1Ord :: Eq SemaphoreCreateFlags
Ord, Ptr b -> Int -> IO SemaphoreCreateFlags
Ptr b -> Int -> SemaphoreCreateFlags -> IO ()
Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags
Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags
Ptr SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags -> IO ()
Ptr SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ()
SemaphoreCreateFlags -> Int
(SemaphoreCreateFlags -> Int)
-> (SemaphoreCreateFlags -> Int)
-> (Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags)
-> (Ptr SemaphoreCreateFlags
    -> Int -> SemaphoreCreateFlags -> IO ())
-> (forall b. Ptr b -> Int -> IO SemaphoreCreateFlags)
-> (forall b. Ptr b -> Int -> SemaphoreCreateFlags -> IO ())
-> (Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags)
-> (Ptr SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ())
-> Storable SemaphoreCreateFlags
forall b. Ptr b -> Int -> IO SemaphoreCreateFlags
forall b. Ptr b -> Int -> SemaphoreCreateFlags -> 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 SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ()
$cpoke :: Ptr SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ()
peek :: Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags
$cpeek :: Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags
pokeByteOff :: Ptr b -> Int -> SemaphoreCreateFlags -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> SemaphoreCreateFlags -> IO ()
peekByteOff :: Ptr b -> Int -> IO SemaphoreCreateFlags
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SemaphoreCreateFlags
pokeElemOff :: Ptr SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags -> IO ()
$cpokeElemOff :: Ptr SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags -> IO ()
peekElemOff :: Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags
$cpeekElemOff :: Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags
alignment :: SemaphoreCreateFlags -> Int
$calignment :: SemaphoreCreateFlags -> Int
sizeOf :: SemaphoreCreateFlags -> Int
$csizeOf :: SemaphoreCreateFlags -> Int
Storable, SemaphoreCreateFlags
SemaphoreCreateFlags -> Zero SemaphoreCreateFlags
forall a. a -> Zero a
zero :: SemaphoreCreateFlags
$czero :: SemaphoreCreateFlags
Zero, Eq SemaphoreCreateFlags
SemaphoreCreateFlags
Eq SemaphoreCreateFlags =>
(SemaphoreCreateFlags
 -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags
    -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags
    -> SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> SemaphoreCreateFlags
-> (Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> Bool)
-> (SemaphoreCreateFlags -> Maybe Int)
-> (SemaphoreCreateFlags -> Int)
-> (SemaphoreCreateFlags -> Bool)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags)
-> (SemaphoreCreateFlags -> Int)
-> Bits SemaphoreCreateFlags
Int -> SemaphoreCreateFlags
SemaphoreCreateFlags -> Bool
SemaphoreCreateFlags -> Int
SemaphoreCreateFlags -> Maybe Int
SemaphoreCreateFlags -> SemaphoreCreateFlags
SemaphoreCreateFlags -> Int -> Bool
SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
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 :: SemaphoreCreateFlags -> Int
$cpopCount :: SemaphoreCreateFlags -> Int
rotateR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$crotateR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
rotateL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$crotateL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
unsafeShiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cunsafeShiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
shiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cshiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
unsafeShiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cunsafeShiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
shiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cshiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
isSigned :: SemaphoreCreateFlags -> Bool
$cisSigned :: SemaphoreCreateFlags -> Bool
bitSize :: SemaphoreCreateFlags -> Int
$cbitSize :: SemaphoreCreateFlags -> Int
bitSizeMaybe :: SemaphoreCreateFlags -> Maybe Int
$cbitSizeMaybe :: SemaphoreCreateFlags -> Maybe Int
testBit :: SemaphoreCreateFlags -> Int -> Bool
$ctestBit :: SemaphoreCreateFlags -> Int -> Bool
complementBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$ccomplementBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
clearBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cclearBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
setBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$csetBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
bit :: Int -> SemaphoreCreateFlags
$cbit :: Int -> SemaphoreCreateFlags
zeroBits :: SemaphoreCreateFlags
$czeroBits :: SemaphoreCreateFlags
rotate :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$crotate :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
shift :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cshift :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
complement :: SemaphoreCreateFlags -> SemaphoreCreateFlags
$ccomplement :: SemaphoreCreateFlags -> SemaphoreCreateFlags
xor :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$cxor :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
.|. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$c.|. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
.&. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$c.&. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$cp1Bits :: Eq SemaphoreCreateFlags
Bits)
instance Show SemaphoreCreateFlags where
  showsPrec :: Int -> SemaphoreCreateFlags -> ShowS
showsPrec p :: Int
p = \case
    SemaphoreCreateFlags x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "SemaphoreCreateFlags 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)
instance Read SemaphoreCreateFlags where
  readPrec :: ReadPrec SemaphoreCreateFlags
readPrec = ReadPrec SemaphoreCreateFlags -> ReadPrec SemaphoreCreateFlags
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec SemaphoreCreateFlags)]
-> ReadPrec SemaphoreCreateFlags
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose []
                     ReadPrec SemaphoreCreateFlags
-> ReadPrec SemaphoreCreateFlags -> ReadPrec SemaphoreCreateFlags
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec SemaphoreCreateFlags -> ReadPrec SemaphoreCreateFlags
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "SemaphoreCreateFlags")
                       Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
                       SemaphoreCreateFlags -> ReadPrec SemaphoreCreateFlags
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> SemaphoreCreateFlags
SemaphoreCreateFlags Flags
v)))