{-# language CPP #-}
module Vulkan.Core11.Enums.MemoryAllocateFlagBits ( MemoryAllocateFlags
, MemoryAllocateFlagBits( MEMORY_ALLOCATE_DEVICE_MASK_BIT
, MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT
, MEMORY_ALLOCATE_DEVICE_ADDRESS_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 MemoryAllocateFlags = MemoryAllocateFlagBits
newtype MemoryAllocateFlagBits = MemoryAllocateFlagBits Flags
deriving newtype (MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
$c/= :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
== :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
$c== :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
Eq, Eq MemoryAllocateFlagBits
MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Ordering
MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
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 :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$cmin :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
max :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$cmax :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
>= :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
$c>= :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
> :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
$c> :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
<= :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
$c<= :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
< :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
$c< :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
compare :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Ordering
$ccompare :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Ordering
Ord, Ptr MemoryAllocateFlagBits -> IO MemoryAllocateFlagBits
Ptr MemoryAllocateFlagBits -> Int -> IO MemoryAllocateFlagBits
Ptr MemoryAllocateFlagBits
-> Int -> MemoryAllocateFlagBits -> IO ()
Ptr MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> IO ()
MemoryAllocateFlagBits -> Int
forall b. Ptr b -> Int -> IO MemoryAllocateFlagBits
forall b. Ptr b -> Int -> MemoryAllocateFlagBits -> 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 MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> IO ()
$cpoke :: Ptr MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> IO ()
peek :: Ptr MemoryAllocateFlagBits -> IO MemoryAllocateFlagBits
$cpeek :: Ptr MemoryAllocateFlagBits -> IO MemoryAllocateFlagBits
pokeByteOff :: forall b. Ptr b -> Int -> MemoryAllocateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MemoryAllocateFlagBits -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO MemoryAllocateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MemoryAllocateFlagBits
pokeElemOff :: Ptr MemoryAllocateFlagBits
-> Int -> MemoryAllocateFlagBits -> IO ()
$cpokeElemOff :: Ptr MemoryAllocateFlagBits
-> Int -> MemoryAllocateFlagBits -> IO ()
peekElemOff :: Ptr MemoryAllocateFlagBits -> Int -> IO MemoryAllocateFlagBits
$cpeekElemOff :: Ptr MemoryAllocateFlagBits -> Int -> IO MemoryAllocateFlagBits
alignment :: MemoryAllocateFlagBits -> Int
$calignment :: MemoryAllocateFlagBits -> Int
sizeOf :: MemoryAllocateFlagBits -> Int
$csizeOf :: MemoryAllocateFlagBits -> Int
Storable, MemoryAllocateFlagBits
forall a. a -> Zero a
zero :: MemoryAllocateFlagBits
$czero :: MemoryAllocateFlagBits
Zero, Eq MemoryAllocateFlagBits
MemoryAllocateFlagBits
Int -> MemoryAllocateFlagBits
MemoryAllocateFlagBits -> Bool
MemoryAllocateFlagBits -> Int
MemoryAllocateFlagBits -> Maybe Int
MemoryAllocateFlagBits -> MemoryAllocateFlagBits
MemoryAllocateFlagBits -> Int -> Bool
MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
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 :: MemoryAllocateFlagBits -> Int
$cpopCount :: MemoryAllocateFlagBits -> Int
rotateR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$crotateR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
rotateL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$crotateL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
unsafeShiftR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cunsafeShiftR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
shiftR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cshiftR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
unsafeShiftL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cunsafeShiftL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
shiftL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cshiftL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
isSigned :: MemoryAllocateFlagBits -> Bool
$cisSigned :: MemoryAllocateFlagBits -> Bool
bitSize :: MemoryAllocateFlagBits -> Int
$cbitSize :: MemoryAllocateFlagBits -> Int
bitSizeMaybe :: MemoryAllocateFlagBits -> Maybe Int
$cbitSizeMaybe :: MemoryAllocateFlagBits -> Maybe Int
testBit :: MemoryAllocateFlagBits -> Int -> Bool
$ctestBit :: MemoryAllocateFlagBits -> Int -> Bool
complementBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$ccomplementBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
clearBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cclearBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
setBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$csetBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
bit :: Int -> MemoryAllocateFlagBits
$cbit :: Int -> MemoryAllocateFlagBits
zeroBits :: MemoryAllocateFlagBits
$czeroBits :: MemoryAllocateFlagBits
rotate :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$crotate :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
shift :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cshift :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
complement :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$ccomplement :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits
xor :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$cxor :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
.|. :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$c.|. :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
.&. :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$c.&. :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
Bits, Bits MemoryAllocateFlagBits
MemoryAllocateFlagBits -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: MemoryAllocateFlagBits -> Int
$ccountTrailingZeros :: MemoryAllocateFlagBits -> Int
countLeadingZeros :: MemoryAllocateFlagBits -> Int
$ccountLeadingZeros :: MemoryAllocateFlagBits -> Int
finiteBitSize :: MemoryAllocateFlagBits -> Int
$cfiniteBitSize :: MemoryAllocateFlagBits -> Int
FiniteBits)
pattern $bMEMORY_ALLOCATE_DEVICE_MASK_BIT :: MemoryAllocateFlagBits
$mMEMORY_ALLOCATE_DEVICE_MASK_BIT :: forall {r}.
MemoryAllocateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_ALLOCATE_DEVICE_MASK_BIT = MemoryAllocateFlagBits 0x00000001
pattern $bMEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT :: MemoryAllocateFlagBits
$mMEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT :: forall {r}.
MemoryAllocateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT = MemoryAllocateFlagBits 0x00000004
pattern $bMEMORY_ALLOCATE_DEVICE_ADDRESS_BIT :: MemoryAllocateFlagBits
$mMEMORY_ALLOCATE_DEVICE_ADDRESS_BIT :: forall {r}.
MemoryAllocateFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT = MemoryAllocateFlagBits 0x00000002
conNameMemoryAllocateFlagBits :: String
conNameMemoryAllocateFlagBits :: String
conNameMemoryAllocateFlagBits = String
"MemoryAllocateFlagBits"
enumPrefixMemoryAllocateFlagBits :: String
enumPrefixMemoryAllocateFlagBits :: String
enumPrefixMemoryAllocateFlagBits = String
"MEMORY_ALLOCATE_DEVICE_"
showTableMemoryAllocateFlagBits :: [(MemoryAllocateFlagBits, String)]
showTableMemoryAllocateFlagBits :: [(MemoryAllocateFlagBits, String)]
showTableMemoryAllocateFlagBits =
[
( MemoryAllocateFlagBits
MEMORY_ALLOCATE_DEVICE_MASK_BIT
, String
"MASK_BIT"
)
,
( MemoryAllocateFlagBits
MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT
, String
"ADDRESS_CAPTURE_REPLAY_BIT"
)
,
( MemoryAllocateFlagBits
MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT
, String
"ADDRESS_BIT"
)
]
instance Show MemoryAllocateFlagBits where
showsPrec :: Int -> MemoryAllocateFlagBits -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixMemoryAllocateFlagBits
[(MemoryAllocateFlagBits, String)]
showTableMemoryAllocateFlagBits
String
conNameMemoryAllocateFlagBits
(\(MemoryAllocateFlagBits 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 MemoryAllocateFlagBits where
readPrec :: ReadPrec MemoryAllocateFlagBits
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixMemoryAllocateFlagBits
[(MemoryAllocateFlagBits, String)]
showTableMemoryAllocateFlagBits
String
conNameMemoryAllocateFlagBits
Flags -> MemoryAllocateFlagBits
MemoryAllocateFlagBits