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