{-# language CPP #-}
module Vulkan.Core10.Enums.SemaphoreCreateFlags (SemaphoreCreateFlags(..)) where
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showString)
import Numeric (showHex)
import Vulkan.Zero (Zero)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Vulkan.Core10.FundamentalTypes (Flags)
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
$c== :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
== :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$c/= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
/= :: 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
$ccompare :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering
compare :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Ordering
$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
>= :: SemaphoreCreateFlags -> SemaphoreCreateFlags -> Bool
$cmax :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
max :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$cmin :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
min :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
Ord, 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
$csizeOf :: SemaphoreCreateFlags -> Int
sizeOf :: SemaphoreCreateFlags -> Int
$calignment :: SemaphoreCreateFlags -> Int
alignment :: SemaphoreCreateFlags -> Int
$cpeekElemOff :: Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags
peekElemOff :: Ptr SemaphoreCreateFlags -> Int -> IO SemaphoreCreateFlags
$cpokeElemOff :: Ptr SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags -> IO ()
pokeElemOff :: Ptr SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO SemaphoreCreateFlags
peekByteOff :: forall b. Ptr b -> Int -> IO SemaphoreCreateFlags
$cpokeByteOff :: forall b. Ptr b -> Int -> SemaphoreCreateFlags -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> SemaphoreCreateFlags -> IO ()
$cpeek :: Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags
peek :: Ptr SemaphoreCreateFlags -> IO SemaphoreCreateFlags
$cpoke :: Ptr SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ()
poke :: Ptr SemaphoreCreateFlags -> SemaphoreCreateFlags -> IO ()
Storable, SemaphoreCreateFlags
SemaphoreCreateFlags -> Zero SemaphoreCreateFlags
forall a. a -> Zero a
$czero :: SemaphoreCreateFlags
zero :: 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
$c.&. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
.&. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$c.|. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
.|. :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$cxor :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
xor :: SemaphoreCreateFlags
-> SemaphoreCreateFlags -> SemaphoreCreateFlags
$ccomplement :: SemaphoreCreateFlags -> SemaphoreCreateFlags
complement :: SemaphoreCreateFlags -> SemaphoreCreateFlags
$cshift :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
shift :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$crotate :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
rotate :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$czeroBits :: SemaphoreCreateFlags
zeroBits :: SemaphoreCreateFlags
$cbit :: Int -> SemaphoreCreateFlags
bit :: Int -> SemaphoreCreateFlags
$csetBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
setBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cclearBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
clearBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$ccomplementBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
complementBit :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$ctestBit :: SemaphoreCreateFlags -> Int -> Bool
testBit :: SemaphoreCreateFlags -> Int -> Bool
$cbitSizeMaybe :: SemaphoreCreateFlags -> Maybe Int
bitSizeMaybe :: SemaphoreCreateFlags -> Maybe Int
$cbitSize :: SemaphoreCreateFlags -> Int
bitSize :: SemaphoreCreateFlags -> Int
$cisSigned :: SemaphoreCreateFlags -> Bool
isSigned :: SemaphoreCreateFlags -> Bool
$cshiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
shiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cunsafeShiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
unsafeShiftL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cshiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
shiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cunsafeShiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
unsafeShiftR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$crotateL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
rotateL :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$crotateR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
rotateR :: SemaphoreCreateFlags -> Int -> SemaphoreCreateFlags
$cpopCount :: SemaphoreCreateFlags -> Int
popCount :: SemaphoreCreateFlags -> Int
Bits, Bits SemaphoreCreateFlags
Bits SemaphoreCreateFlags =>
(SemaphoreCreateFlags -> Int)
-> (SemaphoreCreateFlags -> Int)
-> (SemaphoreCreateFlags -> Int)
-> FiniteBits SemaphoreCreateFlags
SemaphoreCreateFlags -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: SemaphoreCreateFlags -> Int
finiteBitSize :: SemaphoreCreateFlags -> Int
$ccountLeadingZeros :: SemaphoreCreateFlags -> Int
countLeadingZeros :: SemaphoreCreateFlags -> Int
$ccountTrailingZeros :: SemaphoreCreateFlags -> Int
countTrailingZeros :: SemaphoreCreateFlags -> Int
FiniteBits)
conNameSemaphoreCreateFlags :: String
conNameSemaphoreCreateFlags :: String
conNameSemaphoreCreateFlags = String
"SemaphoreCreateFlags"
enumPrefixSemaphoreCreateFlags :: String
enumPrefixSemaphoreCreateFlags :: String
enumPrefixSemaphoreCreateFlags = String
""
showTableSemaphoreCreateFlags :: [(SemaphoreCreateFlags, String)]
showTableSemaphoreCreateFlags :: [(SemaphoreCreateFlags, String)]
showTableSemaphoreCreateFlags = []
instance Show SemaphoreCreateFlags where
showsPrec :: Int -> SemaphoreCreateFlags -> ShowS
showsPrec =
String
-> [(SemaphoreCreateFlags, String)]
-> String
-> (SemaphoreCreateFlags -> Flags)
-> (Flags -> ShowS)
-> Int
-> SemaphoreCreateFlags
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixSemaphoreCreateFlags
[(SemaphoreCreateFlags, String)]
showTableSemaphoreCreateFlags
String
conNameSemaphoreCreateFlags
(\(SemaphoreCreateFlags Flags
x) -> Flags
x)
(\Flags
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. Integral a => a -> ShowS
showHex Flags
x)
instance Read SemaphoreCreateFlags where
readPrec :: ReadPrec SemaphoreCreateFlags
readPrec =
String
-> [(SemaphoreCreateFlags, String)]
-> String
-> (Flags -> SemaphoreCreateFlags)
-> ReadPrec SemaphoreCreateFlags
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixSemaphoreCreateFlags
[(SemaphoreCreateFlags, String)]
showTableSemaphoreCreateFlags
String
conNameSemaphoreCreateFlags
Flags -> SemaphoreCreateFlags
SemaphoreCreateFlags