{-# language CPP #-}
module Vulkan.Core10.Enums.CommandPoolCreateFlagBits ( CommandPoolCreateFlags
, CommandPoolCreateFlagBits( COMMAND_POOL_CREATE_TRANSIENT_BIT
, COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT
, COMMAND_POOL_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 CommandPoolCreateFlags = CommandPoolCreateFlagBits
newtype CommandPoolCreateFlagBits = CommandPoolCreateFlagBits Flags
deriving newtype (CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
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
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
Ord, Ptr CommandPoolCreateFlagBits -> IO CommandPoolCreateFlagBits
Ptr CommandPoolCreateFlagBits
-> Int -> IO CommandPoolCreateFlagBits
Ptr CommandPoolCreateFlagBits
-> Int -> CommandPoolCreateFlagBits -> IO ()
Ptr CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> IO ()
CommandPoolCreateFlagBits -> Int
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 :: forall b. Ptr b -> Int -> CommandPoolCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CommandPoolCreateFlagBits -> IO ()
peekByteOff :: forall b. 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
forall a. a -> Zero a
zero :: CommandPoolCreateFlagBits
$czero :: CommandPoolCreateFlagBits
Zero, Eq CommandPoolCreateFlagBits
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
Bits, Bits CommandPoolCreateFlagBits
CommandPoolCreateFlagBits -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: CommandPoolCreateFlagBits -> Int
$ccountTrailingZeros :: CommandPoolCreateFlagBits -> Int
countLeadingZeros :: CommandPoolCreateFlagBits -> Int
$ccountLeadingZeros :: CommandPoolCreateFlagBits -> Int
finiteBitSize :: CommandPoolCreateFlagBits -> Int
$cfiniteBitSize :: CommandPoolCreateFlagBits -> Int
FiniteBits)
pattern $bCOMMAND_POOL_CREATE_TRANSIENT_BIT :: CommandPoolCreateFlagBits
$mCOMMAND_POOL_CREATE_TRANSIENT_BIT :: forall {r}.
CommandPoolCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
COMMAND_POOL_CREATE_TRANSIENT_BIT = CommandPoolCreateFlagBits 0x00000001
pattern $bCOMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT :: CommandPoolCreateFlagBits
$mCOMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT :: forall {r}.
CommandPoolCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT = CommandPoolCreateFlagBits 0x00000002
pattern $bCOMMAND_POOL_CREATE_PROTECTED_BIT :: CommandPoolCreateFlagBits
$mCOMMAND_POOL_CREATE_PROTECTED_BIT :: forall {r}.
CommandPoolCreateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
COMMAND_POOL_CREATE_PROTECTED_BIT = CommandPoolCreateFlagBits 0x00000004
conNameCommandPoolCreateFlagBits :: String
conNameCommandPoolCreateFlagBits :: String
conNameCommandPoolCreateFlagBits = String
"CommandPoolCreateFlagBits"
enumPrefixCommandPoolCreateFlagBits :: String
enumPrefixCommandPoolCreateFlagBits :: String
enumPrefixCommandPoolCreateFlagBits = String
"COMMAND_POOL_CREATE_"
showTableCommandPoolCreateFlagBits :: [(CommandPoolCreateFlagBits, String)]
showTableCommandPoolCreateFlagBits :: [(CommandPoolCreateFlagBits, String)]
showTableCommandPoolCreateFlagBits =
[
( CommandPoolCreateFlagBits
COMMAND_POOL_CREATE_TRANSIENT_BIT
, String
"TRANSIENT_BIT"
)
,
( CommandPoolCreateFlagBits
COMMAND_POOL_CREATE_RESET_COMMAND_BUFFER_BIT
, String
"RESET_COMMAND_BUFFER_BIT"
)
,
( CommandPoolCreateFlagBits
COMMAND_POOL_CREATE_PROTECTED_BIT
, String
"PROTECTED_BIT"
)
]
instance Show CommandPoolCreateFlagBits where
showsPrec :: Int -> CommandPoolCreateFlagBits -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixCommandPoolCreateFlagBits
[(CommandPoolCreateFlagBits, String)]
showTableCommandPoolCreateFlagBits
String
conNameCommandPoolCreateFlagBits
(\(CommandPoolCreateFlagBits Flags
x) -> Flags
x)
(\Flags
x -> String -> ShowS
showString String
"0x" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)
instance Read CommandPoolCreateFlagBits where
readPrec :: ReadPrec CommandPoolCreateFlagBits
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixCommandPoolCreateFlagBits
[(CommandPoolCreateFlagBits, String)]
showTableCommandPoolCreateFlagBits
String
conNameCommandPoolCreateFlagBits
Flags -> CommandPoolCreateFlagBits
CommandPoolCreateFlagBits