{-# language CPP #-}
-- No documentation found for Chapter "DeviceQueueCreateFlagBits"
module Vulkan.Core10.Enums.DeviceQueueCreateFlagBits  ( DeviceQueueCreateFlags
                                                      , DeviceQueueCreateFlagBits( DEVICE_QUEUE_CREATE_PROTECTED_BIT
                                                                                 , ..
                                                                                 )
                                                      ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import GHC.Show (showString)
import Numeric (showHex)
import Vulkan.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 Vulkan.Core10.FundamentalTypes (Flags)
type DeviceQueueCreateFlags = DeviceQueueCreateFlagBits

-- | VkDeviceQueueCreateFlagBits - Bitmask specifying behavior of the queue
--
-- = See Also
--
-- 'DeviceQueueCreateFlags'
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
/= :: DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits -> Bool
$c/= :: DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits -> Bool
== :: DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits -> Bool
$c== :: 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
min :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
$cmin :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
max :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
$cmax :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
>= :: DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits -> Bool
$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
compare :: DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits -> Ordering
$ccompare :: DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits -> Ordering
$cp1Ord :: Eq DeviceQueueCreateFlagBits
Ord, Ptr b -> Int -> IO DeviceQueueCreateFlagBits
Ptr b -> Int -> DeviceQueueCreateFlagBits -> IO ()
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
poke :: Ptr DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits -> IO ()
$cpoke :: Ptr DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits -> IO ()
peek :: Ptr DeviceQueueCreateFlagBits -> IO DeviceQueueCreateFlagBits
$cpeek :: Ptr DeviceQueueCreateFlagBits -> IO DeviceQueueCreateFlagBits
pokeByteOff :: Ptr b -> Int -> DeviceQueueCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DeviceQueueCreateFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO DeviceQueueCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DeviceQueueCreateFlagBits
pokeElemOff :: Ptr DeviceQueueCreateFlagBits
-> Int -> DeviceQueueCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr DeviceQueueCreateFlagBits
-> Int -> DeviceQueueCreateFlagBits -> IO ()
peekElemOff :: Ptr DeviceQueueCreateFlagBits
-> Int -> IO DeviceQueueCreateFlagBits
$cpeekElemOff :: Ptr DeviceQueueCreateFlagBits
-> Int -> IO DeviceQueueCreateFlagBits
alignment :: DeviceQueueCreateFlagBits -> Int
$calignment :: DeviceQueueCreateFlagBits -> Int
sizeOf :: DeviceQueueCreateFlagBits -> Int
$csizeOf :: DeviceQueueCreateFlagBits -> Int
Storable, DeviceQueueCreateFlagBits
DeviceQueueCreateFlagBits -> Zero DeviceQueueCreateFlagBits
forall a. a -> Zero a
zero :: DeviceQueueCreateFlagBits
$czero :: 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
popCount :: DeviceQueueCreateFlagBits -> Int
$cpopCount :: DeviceQueueCreateFlagBits -> Int
rotateR :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$crotateR :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
rotateL :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$crotateL :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
unsafeShiftR :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$cunsafeShiftR :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
shiftR :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$cshiftR :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
unsafeShiftL :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$cunsafeShiftL :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
shiftL :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$cshiftL :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
isSigned :: DeviceQueueCreateFlagBits -> Bool
$cisSigned :: DeviceQueueCreateFlagBits -> Bool
bitSize :: DeviceQueueCreateFlagBits -> Int
$cbitSize :: DeviceQueueCreateFlagBits -> Int
bitSizeMaybe :: DeviceQueueCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: DeviceQueueCreateFlagBits -> Maybe Int
testBit :: DeviceQueueCreateFlagBits -> Int -> Bool
$ctestBit :: DeviceQueueCreateFlagBits -> Int -> Bool
complementBit :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$ccomplementBit :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
clearBit :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$cclearBit :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
setBit :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$csetBit :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
bit :: Int -> DeviceQueueCreateFlagBits
$cbit :: Int -> DeviceQueueCreateFlagBits
zeroBits :: DeviceQueueCreateFlagBits
$czeroBits :: DeviceQueueCreateFlagBits
rotate :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$crotate :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
shift :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
$cshift :: DeviceQueueCreateFlagBits -> Int -> DeviceQueueCreateFlagBits
complement :: DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
$ccomplement :: DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
xor :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
$cxor :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
.|. :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
$c.|. :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
.&. :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
$c.&. :: DeviceQueueCreateFlagBits
-> DeviceQueueCreateFlagBits -> DeviceQueueCreateFlagBits
$cp1Bits :: Eq DeviceQueueCreateFlagBits
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
countTrailingZeros :: DeviceQueueCreateFlagBits -> Int
$ccountTrailingZeros :: DeviceQueueCreateFlagBits -> Int
countLeadingZeros :: DeviceQueueCreateFlagBits -> Int
$ccountLeadingZeros :: DeviceQueueCreateFlagBits -> Int
finiteBitSize :: DeviceQueueCreateFlagBits -> Int
$cfiniteBitSize :: DeviceQueueCreateFlagBits -> Int
$cp1FiniteBits :: Bits DeviceQueueCreateFlagBits
FiniteBits)

-- | 'DEVICE_QUEUE_CREATE_PROTECTED_BIT' specifies that the device queue is a
-- protected-capable queue.
pattern $bDEVICE_QUEUE_CREATE_PROTECTED_BIT :: DeviceQueueCreateFlagBits
$mDEVICE_QUEUE_CREATE_PROTECTED_BIT :: forall r.
DeviceQueueCreateFlagBits -> (Void# -> r) -> (Void# -> 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, Show 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