{-# language CPP #-}
module Vulkan.Core10.Enums.CommandPoolCreateFlagBits  ( CommandPoolCreateFlagBits( COMMAND_POOL_CREATE_TRANSIENT_BIT
                                                                                 , COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT
                                                                                 , COMMAND_POOL_CREATE_PROTECTED_BIT
                                                                                 , ..
                                                                                 )
                                                      , CommandPoolCreateFlags
                                                      ) 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)
-- | VkCommandPoolCreateFlagBits - Bitmask specifying usage behavior for a
-- command pool
--
-- = See Also
--
-- 'CommandPoolCreateFlags'
newtype CommandPoolCreateFlagBits = CommandPoolCreateFlagBits Flags
  deriving newtype (CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
(CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool)
-> (CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool)
-> Eq CommandPoolCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
$c/= :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
== :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
$c== :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
Eq, Eq CommandPoolCreateFlagBits
Eq CommandPoolCreateFlagBits =>
(CommandPoolCreateFlagBits
 -> CommandPoolCreateFlagBits -> Ordering)
-> (CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool)
-> (CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool)
-> (CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool)
-> (CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool)
-> (CommandPoolCreateFlagBits
    -> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits
    -> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits)
-> Ord CommandPoolCreateFlagBits
CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Ordering
CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
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 :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$cmin :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
max :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$cmax :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
>= :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
$c>= :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
> :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
$c> :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
<= :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
$c<= :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
< :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
$c< :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
compare :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Ordering
$ccompare :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Ordering
$cp1Ord :: Eq CommandPoolCreateFlagBits
Ord, Ptr b -> Int -> IO CommandPoolCreateFlagBits
Ptr b -> Int -> CommandPoolCreateFlagBits -> IO ()
Ptr CommandPoolCreateFlagBits -> IO CommandPoolCreateFlagBits
Ptr CommandPoolCreateFlagBits
-> Int -> IO CommandPoolCreateFlagBits
Ptr CommandPoolCreateFlagBits
-> Int -> CommandPoolCreateFlagBits -> IO ()
Ptr CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> IO ()
CommandPoolCreateFlagBits -> Int
(CommandPoolCreateFlagBits -> Int)
-> (CommandPoolCreateFlagBits -> Int)
-> (Ptr CommandPoolCreateFlagBits
    -> Int -> IO CommandPoolCreateFlagBits)
-> (Ptr CommandPoolCreateFlagBits
    -> Int -> CommandPoolCreateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO CommandPoolCreateFlagBits)
-> (forall b. Ptr b -> Int -> CommandPoolCreateFlagBits -> IO ())
-> (Ptr CommandPoolCreateFlagBits -> IO CommandPoolCreateFlagBits)
-> (Ptr CommandPoolCreateFlagBits
    -> CommandPoolCreateFlagBits -> IO ())
-> Storable CommandPoolCreateFlagBits
forall b. Ptr b -> Int -> IO CommandPoolCreateFlagBits
forall b. Ptr b -> Int -> CommandPoolCreateFlagBits -> 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 CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> IO ()
$cpoke :: Ptr CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> IO ()
peek :: Ptr CommandPoolCreateFlagBits -> IO CommandPoolCreateFlagBits
$cpeek :: Ptr CommandPoolCreateFlagBits -> IO CommandPoolCreateFlagBits
pokeByteOff :: Ptr b -> Int -> CommandPoolCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CommandPoolCreateFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO CommandPoolCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CommandPoolCreateFlagBits
pokeElemOff :: Ptr CommandPoolCreateFlagBits
-> Int -> CommandPoolCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr CommandPoolCreateFlagBits
-> Int -> CommandPoolCreateFlagBits -> IO ()
peekElemOff :: Ptr CommandPoolCreateFlagBits
-> Int -> IO CommandPoolCreateFlagBits
$cpeekElemOff :: Ptr CommandPoolCreateFlagBits
-> Int -> IO CommandPoolCreateFlagBits
alignment :: CommandPoolCreateFlagBits -> Int
$calignment :: CommandPoolCreateFlagBits -> Int
sizeOf :: CommandPoolCreateFlagBits -> Int
$csizeOf :: CommandPoolCreateFlagBits -> Int
Storable, CommandPoolCreateFlagBits
CommandPoolCreateFlagBits -> Zero CommandPoolCreateFlagBits
forall a. a -> Zero a
zero :: CommandPoolCreateFlagBits
$czero :: CommandPoolCreateFlagBits
Zero, Eq CommandPoolCreateFlagBits
CommandPoolCreateFlagBits
Eq CommandPoolCreateFlagBits =>
(CommandPoolCreateFlagBits
 -> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits
    -> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits
    -> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> CommandPoolCreateFlagBits
-> (Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> Bool)
-> (CommandPoolCreateFlagBits -> Maybe Int)
-> (CommandPoolCreateFlagBits -> Int)
-> (CommandPoolCreateFlagBits -> Bool)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits)
-> (CommandPoolCreateFlagBits -> Int)
-> Bits CommandPoolCreateFlagBits
Int -> CommandPoolCreateFlagBits
CommandPoolCreateFlagBits -> Bool
CommandPoolCreateFlagBits -> Int
CommandPoolCreateFlagBits -> Maybe Int
CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
CommandPoolCreateFlagBits -> Int -> Bool
CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
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 :: CommandPoolCreateFlagBits -> Int
$cpopCount :: CommandPoolCreateFlagBits -> Int
rotateR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$crotateR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
rotateL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$crotateL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
unsafeShiftR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cunsafeShiftR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
shiftR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cshiftR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
unsafeShiftL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cunsafeShiftL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
shiftL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cshiftL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
isSigned :: CommandPoolCreateFlagBits -> Bool
$cisSigned :: CommandPoolCreateFlagBits -> Bool
bitSize :: CommandPoolCreateFlagBits -> Int
$cbitSize :: CommandPoolCreateFlagBits -> Int
bitSizeMaybe :: CommandPoolCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: CommandPoolCreateFlagBits -> Maybe Int
testBit :: CommandPoolCreateFlagBits -> Int -> Bool
$ctestBit :: CommandPoolCreateFlagBits -> Int -> Bool
complementBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$ccomplementBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
clearBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cclearBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
setBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$csetBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
bit :: Int -> CommandPoolCreateFlagBits
$cbit :: Int -> CommandPoolCreateFlagBits
zeroBits :: CommandPoolCreateFlagBits
$czeroBits :: CommandPoolCreateFlagBits
rotate :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$crotate :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
shift :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cshift :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
complement :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$ccomplement :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
xor :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$cxor :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
.|. :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$c.|. :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
.&. :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$c.&. :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$cp1Bits :: Eq CommandPoolCreateFlagBits
Bits)

-- | 'COMMAND_POOL_CREATE_TRANSIENT_BIT' specifies that command buffers
-- allocated from the pool will be short-lived, meaning that they will be
-- reset or freed in a relatively short timeframe. This flag /may/ be used
-- by the implementation to control memory allocation behavior within the
-- pool.
pattern $bCOMMAND_POOL_CREATE_TRANSIENT_BIT :: CommandPoolCreateFlagBits
$mCOMMAND_POOL_CREATE_TRANSIENT_BIT :: forall r.
CommandPoolCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
COMMAND_POOL_CREATE_TRANSIENT_BIT = CommandPoolCreateFlagBits 0x00000001
-- | 'COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT' allows any command buffer
-- allocated from a pool to be individually reset to the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle initial state>;
-- either by calling 'Vulkan.Core10.CommandBuffer.resetCommandBuffer', or
-- via the implicit reset when calling
-- 'Vulkan.Core10.CommandBuffer.beginCommandBuffer'. If this flag is not
-- set on a pool, then 'Vulkan.Core10.CommandBuffer.resetCommandBuffer'
-- /must/ not be called for any command buffer allocated from that pool.
pattern $bCOMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT :: CommandPoolCreateFlagBits
$mCOMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT :: forall r.
CommandPoolCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT = CommandPoolCreateFlagBits 0x00000002
-- | 'COMMAND_POOL_CREATE_PROTECTED_BIT' specifies that command buffers
-- allocated from the pool are protected command buffers.
pattern $bCOMMAND_POOL_CREATE_PROTECTED_BIT :: CommandPoolCreateFlagBits
$mCOMMAND_POOL_CREATE_PROTECTED_BIT :: forall r.
CommandPoolCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
COMMAND_POOL_CREATE_PROTECTED_BIT = CommandPoolCreateFlagBits 0x00000004

type CommandPoolCreateFlags = CommandPoolCreateFlagBits

instance Show CommandPoolCreateFlagBits where
  showsPrec :: Int -> CommandPoolCreateFlagBits -> ShowS
showsPrec p :: Int
p = \case
    COMMAND_POOL_CREATE_TRANSIENT_BIT -> String -> ShowS
showString "COMMAND_POOL_CREATE_TRANSIENT_BIT"
    COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT -> String -> ShowS
showString "COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT"
    COMMAND_POOL_CREATE_PROTECTED_BIT -> String -> ShowS
showString "COMMAND_POOL_CREATE_PROTECTED_BIT"
    CommandPoolCreateFlagBits x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "CommandPoolCreateFlagBits 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 CommandPoolCreateFlagBits where
  readPrec :: ReadPrec CommandPoolCreateFlagBits
readPrec = ReadPrec CommandPoolCreateFlagBits
-> ReadPrec CommandPoolCreateFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec CommandPoolCreateFlagBits)]
-> ReadPrec CommandPoolCreateFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("COMMAND_POOL_CREATE_TRANSIENT_BIT", CommandPoolCreateFlagBits -> ReadPrec CommandPoolCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure CommandPoolCreateFlagBits
COMMAND_POOL_CREATE_TRANSIENT_BIT)
                            , ("COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT", CommandPoolCreateFlagBits -> ReadPrec CommandPoolCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure CommandPoolCreateFlagBits
COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT)
                            , ("COMMAND_POOL_CREATE_PROTECTED_BIT", CommandPoolCreateFlagBits -> ReadPrec CommandPoolCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure CommandPoolCreateFlagBits
COMMAND_POOL_CREATE_PROTECTED_BIT)]
                     ReadPrec CommandPoolCreateFlagBits
-> ReadPrec CommandPoolCreateFlagBits
-> ReadPrec CommandPoolCreateFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec CommandPoolCreateFlagBits
-> ReadPrec CommandPoolCreateFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "CommandPoolCreateFlagBits")
                       Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
                       CommandPoolCreateFlagBits -> ReadPrec CommandPoolCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> CommandPoolCreateFlagBits
CommandPoolCreateFlagBits Flags
v)))