{-# language CPP #-}
-- No documentation found for Chapter "QueueFlagBits"
module Vulkan.Core10.Enums.QueueFlagBits  ( QueueFlags
                                          , QueueFlagBits( QUEUE_GRAPHICS_BIT
                                                         , QUEUE_COMPUTE_BIT
                                                         , QUEUE_TRANSFER_BIT
                                                         , QUEUE_SPARSE_BINDING_BIT
                                                         , QUEUE_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 QueueFlags = QueueFlagBits

-- | VkQueueFlagBits - Bitmask specifying capabilities of queues in a queue
-- family
--
-- = Description
--
-- If an implementation exposes any queue family that supports graphics
-- operations, at least one queue family of at least one physical device
-- exposed by the implementation /must/ support both graphics and compute
-- operations.
--
-- Furthermore, if the protected memory physical device feature is
-- supported, then at least one queue family of at least one physical
-- device exposed by the implementation /must/ support graphics operations,
-- compute operations, and protected memory operations.
--
-- Note
--
-- All commands that are allowed on a queue that supports transfer
-- operations are also allowed on a queue that supports either graphics or
-- compute operations. Thus, if the capabilities of a queue family include
-- 'QUEUE_GRAPHICS_BIT' or 'QUEUE_COMPUTE_BIT', then reporting the
-- 'QUEUE_TRANSFER_BIT' capability separately for that queue family is
-- /optional/.
--
-- For further details see
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#devsandqueues-queues Queues>.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'QueueFlags'
newtype QueueFlagBits = QueueFlagBits Flags
  deriving newtype (QueueFlagBits -> QueueFlagBits -> Bool
(QueueFlagBits -> QueueFlagBits -> Bool)
-> (QueueFlagBits -> QueueFlagBits -> Bool) -> Eq QueueFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueueFlagBits -> QueueFlagBits -> Bool
$c/= :: QueueFlagBits -> QueueFlagBits -> Bool
== :: QueueFlagBits -> QueueFlagBits -> Bool
$c== :: QueueFlagBits -> QueueFlagBits -> Bool
Eq, Eq QueueFlagBits
Eq QueueFlagBits
-> (QueueFlagBits -> QueueFlagBits -> Ordering)
-> (QueueFlagBits -> QueueFlagBits -> Bool)
-> (QueueFlagBits -> QueueFlagBits -> Bool)
-> (QueueFlagBits -> QueueFlagBits -> Bool)
-> (QueueFlagBits -> QueueFlagBits -> Bool)
-> (QueueFlagBits -> QueueFlagBits -> QueueFlagBits)
-> (QueueFlagBits -> QueueFlagBits -> QueueFlagBits)
-> Ord QueueFlagBits
QueueFlagBits -> QueueFlagBits -> Bool
QueueFlagBits -> QueueFlagBits -> Ordering
QueueFlagBits -> QueueFlagBits -> QueueFlagBits
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 :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
$cmin :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
max :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
$cmax :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
>= :: QueueFlagBits -> QueueFlagBits -> Bool
$c>= :: QueueFlagBits -> QueueFlagBits -> Bool
> :: QueueFlagBits -> QueueFlagBits -> Bool
$c> :: QueueFlagBits -> QueueFlagBits -> Bool
<= :: QueueFlagBits -> QueueFlagBits -> Bool
$c<= :: QueueFlagBits -> QueueFlagBits -> Bool
< :: QueueFlagBits -> QueueFlagBits -> Bool
$c< :: QueueFlagBits -> QueueFlagBits -> Bool
compare :: QueueFlagBits -> QueueFlagBits -> Ordering
$ccompare :: QueueFlagBits -> QueueFlagBits -> Ordering
$cp1Ord :: Eq QueueFlagBits
Ord, Ptr b -> Int -> IO QueueFlagBits
Ptr b -> Int -> QueueFlagBits -> IO ()
Ptr QueueFlagBits -> IO QueueFlagBits
Ptr QueueFlagBits -> Int -> IO QueueFlagBits
Ptr QueueFlagBits -> Int -> QueueFlagBits -> IO ()
Ptr QueueFlagBits -> QueueFlagBits -> IO ()
QueueFlagBits -> Int
(QueueFlagBits -> Int)
-> (QueueFlagBits -> Int)
-> (Ptr QueueFlagBits -> Int -> IO QueueFlagBits)
-> (Ptr QueueFlagBits -> Int -> QueueFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO QueueFlagBits)
-> (forall b. Ptr b -> Int -> QueueFlagBits -> IO ())
-> (Ptr QueueFlagBits -> IO QueueFlagBits)
-> (Ptr QueueFlagBits -> QueueFlagBits -> IO ())
-> Storable QueueFlagBits
forall b. Ptr b -> Int -> IO QueueFlagBits
forall b. Ptr b -> Int -> QueueFlagBits -> 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 QueueFlagBits -> QueueFlagBits -> IO ()
$cpoke :: Ptr QueueFlagBits -> QueueFlagBits -> IO ()
peek :: Ptr QueueFlagBits -> IO QueueFlagBits
$cpeek :: Ptr QueueFlagBits -> IO QueueFlagBits
pokeByteOff :: Ptr b -> Int -> QueueFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> QueueFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO QueueFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO QueueFlagBits
pokeElemOff :: Ptr QueueFlagBits -> Int -> QueueFlagBits -> IO ()
$cpokeElemOff :: Ptr QueueFlagBits -> Int -> QueueFlagBits -> IO ()
peekElemOff :: Ptr QueueFlagBits -> Int -> IO QueueFlagBits
$cpeekElemOff :: Ptr QueueFlagBits -> Int -> IO QueueFlagBits
alignment :: QueueFlagBits -> Int
$calignment :: QueueFlagBits -> Int
sizeOf :: QueueFlagBits -> Int
$csizeOf :: QueueFlagBits -> Int
Storable, QueueFlagBits
QueueFlagBits -> Zero QueueFlagBits
forall a. a -> Zero a
zero :: QueueFlagBits
$czero :: QueueFlagBits
Zero, Eq QueueFlagBits
QueueFlagBits
Eq QueueFlagBits
-> (QueueFlagBits -> QueueFlagBits -> QueueFlagBits)
-> (QueueFlagBits -> QueueFlagBits -> QueueFlagBits)
-> (QueueFlagBits -> QueueFlagBits -> QueueFlagBits)
-> (QueueFlagBits -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> QueueFlagBits
-> (Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> Bool)
-> (QueueFlagBits -> Maybe Int)
-> (QueueFlagBits -> Int)
-> (QueueFlagBits -> Bool)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int -> QueueFlagBits)
-> (QueueFlagBits -> Int)
-> Bits QueueFlagBits
Int -> QueueFlagBits
QueueFlagBits -> Bool
QueueFlagBits -> Int
QueueFlagBits -> Maybe Int
QueueFlagBits -> QueueFlagBits
QueueFlagBits -> Int -> Bool
QueueFlagBits -> Int -> QueueFlagBits
QueueFlagBits -> QueueFlagBits -> QueueFlagBits
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 :: QueueFlagBits -> Int
$cpopCount :: QueueFlagBits -> Int
rotateR :: QueueFlagBits -> Int -> QueueFlagBits
$crotateR :: QueueFlagBits -> Int -> QueueFlagBits
rotateL :: QueueFlagBits -> Int -> QueueFlagBits
$crotateL :: QueueFlagBits -> Int -> QueueFlagBits
unsafeShiftR :: QueueFlagBits -> Int -> QueueFlagBits
$cunsafeShiftR :: QueueFlagBits -> Int -> QueueFlagBits
shiftR :: QueueFlagBits -> Int -> QueueFlagBits
$cshiftR :: QueueFlagBits -> Int -> QueueFlagBits
unsafeShiftL :: QueueFlagBits -> Int -> QueueFlagBits
$cunsafeShiftL :: QueueFlagBits -> Int -> QueueFlagBits
shiftL :: QueueFlagBits -> Int -> QueueFlagBits
$cshiftL :: QueueFlagBits -> Int -> QueueFlagBits
isSigned :: QueueFlagBits -> Bool
$cisSigned :: QueueFlagBits -> Bool
bitSize :: QueueFlagBits -> Int
$cbitSize :: QueueFlagBits -> Int
bitSizeMaybe :: QueueFlagBits -> Maybe Int
$cbitSizeMaybe :: QueueFlagBits -> Maybe Int
testBit :: QueueFlagBits -> Int -> Bool
$ctestBit :: QueueFlagBits -> Int -> Bool
complementBit :: QueueFlagBits -> Int -> QueueFlagBits
$ccomplementBit :: QueueFlagBits -> Int -> QueueFlagBits
clearBit :: QueueFlagBits -> Int -> QueueFlagBits
$cclearBit :: QueueFlagBits -> Int -> QueueFlagBits
setBit :: QueueFlagBits -> Int -> QueueFlagBits
$csetBit :: QueueFlagBits -> Int -> QueueFlagBits
bit :: Int -> QueueFlagBits
$cbit :: Int -> QueueFlagBits
zeroBits :: QueueFlagBits
$czeroBits :: QueueFlagBits
rotate :: QueueFlagBits -> Int -> QueueFlagBits
$crotate :: QueueFlagBits -> Int -> QueueFlagBits
shift :: QueueFlagBits -> Int -> QueueFlagBits
$cshift :: QueueFlagBits -> Int -> QueueFlagBits
complement :: QueueFlagBits -> QueueFlagBits
$ccomplement :: QueueFlagBits -> QueueFlagBits
xor :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
$cxor :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
.|. :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
$c.|. :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
.&. :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
$c.&. :: QueueFlagBits -> QueueFlagBits -> QueueFlagBits
$cp1Bits :: Eq QueueFlagBits
Bits, Bits QueueFlagBits
Bits QueueFlagBits
-> (QueueFlagBits -> Int)
-> (QueueFlagBits -> Int)
-> (QueueFlagBits -> Int)
-> FiniteBits QueueFlagBits
QueueFlagBits -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: QueueFlagBits -> Int
$ccountTrailingZeros :: QueueFlagBits -> Int
countLeadingZeros :: QueueFlagBits -> Int
$ccountLeadingZeros :: QueueFlagBits -> Int
finiteBitSize :: QueueFlagBits -> Int
$cfiniteBitSize :: QueueFlagBits -> Int
$cp1FiniteBits :: Bits QueueFlagBits
FiniteBits)

-- | 'QUEUE_GRAPHICS_BIT' specifies that queues in this queue family support
-- graphics operations.
pattern $bQUEUE_GRAPHICS_BIT :: QueueFlagBits
$mQUEUE_GRAPHICS_BIT :: forall r. QueueFlagBits -> (Void# -> r) -> (Void# -> r) -> r
QUEUE_GRAPHICS_BIT       = QueueFlagBits 0x00000001
-- | 'QUEUE_COMPUTE_BIT' specifies that queues in this queue family support
-- compute operations.
pattern $bQUEUE_COMPUTE_BIT :: QueueFlagBits
$mQUEUE_COMPUTE_BIT :: forall r. QueueFlagBits -> (Void# -> r) -> (Void# -> r) -> r
QUEUE_COMPUTE_BIT        = QueueFlagBits 0x00000002
-- | 'QUEUE_TRANSFER_BIT' specifies that queues in this queue family support
-- transfer operations.
pattern $bQUEUE_TRANSFER_BIT :: QueueFlagBits
$mQUEUE_TRANSFER_BIT :: forall r. QueueFlagBits -> (Void# -> r) -> (Void# -> r) -> r
QUEUE_TRANSFER_BIT       = QueueFlagBits 0x00000004
-- | 'QUEUE_SPARSE_BINDING_BIT' specifies that queues in this queue family
-- support sparse memory management operations (see
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#sparsememory Sparse Resources>).
-- If any of the sparse resource features are enabled, then at least one
-- queue family /must/ support this bit.
pattern $bQUEUE_SPARSE_BINDING_BIT :: QueueFlagBits
$mQUEUE_SPARSE_BINDING_BIT :: forall r. QueueFlagBits -> (Void# -> r) -> (Void# -> r) -> r
QUEUE_SPARSE_BINDING_BIT = QueueFlagBits 0x00000008
-- | 'QUEUE_PROTECTED_BIT' specifies that queues in this queue family support
-- the
-- 'Vulkan.Core10.Enums.DeviceQueueCreateFlagBits.DEVICE_QUEUE_CREATE_PROTECTED_BIT'
-- bit. (see
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-protected-memory Protected Memory>).
-- If the physical device supports the @protectedMemory@ feature, at least
-- one of its queue families /must/ support this bit.
pattern $bQUEUE_PROTECTED_BIT :: QueueFlagBits
$mQUEUE_PROTECTED_BIT :: forall r. QueueFlagBits -> (Void# -> r) -> (Void# -> r) -> r
QUEUE_PROTECTED_BIT      = QueueFlagBits 0x00000010

conNameQueueFlagBits :: String
conNameQueueFlagBits :: String
conNameQueueFlagBits = String
"QueueFlagBits"

enumPrefixQueueFlagBits :: String
enumPrefixQueueFlagBits :: String
enumPrefixQueueFlagBits = String
"QUEUE_"

showTableQueueFlagBits :: [(QueueFlagBits, String)]
showTableQueueFlagBits :: [(QueueFlagBits, String)]
showTableQueueFlagBits =
  [ (QueueFlagBits
QUEUE_GRAPHICS_BIT      , String
"GRAPHICS_BIT")
  , (QueueFlagBits
QUEUE_COMPUTE_BIT       , String
"COMPUTE_BIT")
  , (QueueFlagBits
QUEUE_TRANSFER_BIT      , String
"TRANSFER_BIT")
  , (QueueFlagBits
QUEUE_SPARSE_BINDING_BIT, String
"SPARSE_BINDING_BIT")
  , (QueueFlagBits
QUEUE_PROTECTED_BIT     , String
"PROTECTED_BIT")
  ]

instance Show QueueFlagBits where
  showsPrec :: Int -> QueueFlagBits -> ShowS
showsPrec = String
-> [(QueueFlagBits, String)]
-> String
-> (QueueFlagBits -> Flags)
-> (Flags -> ShowS)
-> Int
-> QueueFlagBits
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixQueueFlagBits
                            [(QueueFlagBits, String)]
showTableQueueFlagBits
                            String
conNameQueueFlagBits
                            (\(QueueFlagBits 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 QueueFlagBits where
  readPrec :: ReadPrec QueueFlagBits
readPrec = String
-> [(QueueFlagBits, String)]
-> String
-> (Flags -> QueueFlagBits)
-> ReadPrec QueueFlagBits
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixQueueFlagBits [(QueueFlagBits, String)]
showTableQueueFlagBits String
conNameQueueFlagBits Flags -> QueueFlagBits
QueueFlagBits