{-# 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
(CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool)
-> (CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool)
-> Eq CommandPoolCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
== :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
$c/= :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
/= :: 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
$ccompare :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Ordering
compare :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Ordering
$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
>= :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> Bool
$cmax :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
max :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$cmin :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
min :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
Ord, 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
$csizeOf :: CommandPoolCreateFlagBits -> Int
sizeOf :: CommandPoolCreateFlagBits -> Int
$calignment :: CommandPoolCreateFlagBits -> Int
alignment :: CommandPoolCreateFlagBits -> Int
$cpeekElemOff :: Ptr CommandPoolCreateFlagBits
-> Int -> IO CommandPoolCreateFlagBits
peekElemOff :: Ptr CommandPoolCreateFlagBits
-> Int -> IO CommandPoolCreateFlagBits
$cpokeElemOff :: Ptr CommandPoolCreateFlagBits
-> Int -> CommandPoolCreateFlagBits -> IO ()
pokeElemOff :: Ptr CommandPoolCreateFlagBits
-> Int -> CommandPoolCreateFlagBits -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CommandPoolCreateFlagBits
peekByteOff :: forall b. Ptr b -> Int -> IO CommandPoolCreateFlagBits
$cpokeByteOff :: forall b. Ptr b -> Int -> CommandPoolCreateFlagBits -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> CommandPoolCreateFlagBits -> IO ()
$cpeek :: Ptr CommandPoolCreateFlagBits -> IO CommandPoolCreateFlagBits
peek :: Ptr CommandPoolCreateFlagBits -> IO CommandPoolCreateFlagBits
$cpoke :: Ptr CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> IO ()
poke :: Ptr CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits -> IO ()
Storable, CommandPoolCreateFlagBits
CommandPoolCreateFlagBits -> Zero CommandPoolCreateFlagBits
forall a. a -> Zero a
$czero :: CommandPoolCreateFlagBits
zero :: 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
$c.&. :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
.&. :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$c.|. :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
.|. :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$cxor :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
xor :: CommandPoolCreateFlagBits
-> CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$ccomplement :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
complement :: CommandPoolCreateFlagBits -> CommandPoolCreateFlagBits
$cshift :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
shift :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$crotate :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
rotate :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$czeroBits :: CommandPoolCreateFlagBits
zeroBits :: CommandPoolCreateFlagBits
$cbit :: Int -> CommandPoolCreateFlagBits
bit :: Int -> CommandPoolCreateFlagBits
$csetBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
setBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cclearBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
clearBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$ccomplementBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
complementBit :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$ctestBit :: CommandPoolCreateFlagBits -> Int -> Bool
testBit :: CommandPoolCreateFlagBits -> Int -> Bool
$cbitSizeMaybe :: CommandPoolCreateFlagBits -> Maybe Int
bitSizeMaybe :: CommandPoolCreateFlagBits -> Maybe Int
$cbitSize :: CommandPoolCreateFlagBits -> Int
bitSize :: CommandPoolCreateFlagBits -> Int
$cisSigned :: CommandPoolCreateFlagBits -> Bool
isSigned :: CommandPoolCreateFlagBits -> Bool
$cshiftL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
shiftL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cunsafeShiftL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
unsafeShiftL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cshiftR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
shiftR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cunsafeShiftR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
unsafeShiftR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$crotateL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
rotateL :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$crotateR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
rotateR :: CommandPoolCreateFlagBits -> Int -> CommandPoolCreateFlagBits
$cpopCount :: CommandPoolCreateFlagBits -> Int
popCount :: CommandPoolCreateFlagBits -> Int
Bits, Bits CommandPoolCreateFlagBits
Bits CommandPoolCreateFlagBits =>
(CommandPoolCreateFlagBits -> Int)
-> (CommandPoolCreateFlagBits -> Int)
-> (CommandPoolCreateFlagBits -> Int)
-> FiniteBits CommandPoolCreateFlagBits
CommandPoolCreateFlagBits -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: CommandPoolCreateFlagBits -> Int
finiteBitSize :: CommandPoolCreateFlagBits -> Int
$ccountLeadingZeros :: CommandPoolCreateFlagBits -> Int
countLeadingZeros :: CommandPoolCreateFlagBits -> Int
$ccountTrailingZeros :: CommandPoolCreateFlagBits -> Int
countTrailingZeros :: 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 =
String
-> [(CommandPoolCreateFlagBits, String)]
-> String
-> (CommandPoolCreateFlagBits -> Flags)
-> (Flags -> ShowS)
-> Int
-> CommandPoolCreateFlagBits
-> ShowS
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" 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 CommandPoolCreateFlagBits where
readPrec :: ReadPrec CommandPoolCreateFlagBits
readPrec =
String
-> [(CommandPoolCreateFlagBits, String)]
-> String
-> (Flags -> CommandPoolCreateFlagBits)
-> ReadPrec CommandPoolCreateFlagBits
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixCommandPoolCreateFlagBits
[(CommandPoolCreateFlagBits, String)]
showTableCommandPoolCreateFlagBits
String
conNameCommandPoolCreateFlagBits
Flags -> CommandPoolCreateFlagBits
CommandPoolCreateFlagBits