{-# language CPP #-}
module Vulkan.Core10.Enums.MemoryHeapFlagBits ( MemoryHeapFlags
, MemoryHeapFlagBits( MEMORY_HEAP_DEVICE_LOCAL_BIT
, MEMORY_HEAP_SEU_SAFE_BIT
, MEMORY_HEAP_MULTI_INSTANCE_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 MemoryHeapFlags = MemoryHeapFlagBits
newtype MemoryHeapFlagBits = MemoryHeapFlagBits Flags
deriving newtype (MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
$c/= :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
== :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
$c== :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
Eq, Eq MemoryHeapFlagBits
MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
MemoryHeapFlagBits -> MemoryHeapFlagBits -> Ordering
MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
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 :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
$cmin :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
max :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
$cmax :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
>= :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
$c>= :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
> :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
$c> :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
<= :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
$c<= :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
< :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
$c< :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Bool
compare :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Ordering
$ccompare :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> Ordering
Ord, Ptr MemoryHeapFlagBits -> IO MemoryHeapFlagBits
Ptr MemoryHeapFlagBits -> Int -> IO MemoryHeapFlagBits
Ptr MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits -> IO ()
Ptr MemoryHeapFlagBits -> MemoryHeapFlagBits -> IO ()
MemoryHeapFlagBits -> Int
forall b. Ptr b -> Int -> IO MemoryHeapFlagBits
forall b. Ptr b -> Int -> MemoryHeapFlagBits -> 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 MemoryHeapFlagBits -> MemoryHeapFlagBits -> IO ()
$cpoke :: Ptr MemoryHeapFlagBits -> MemoryHeapFlagBits -> IO ()
peek :: Ptr MemoryHeapFlagBits -> IO MemoryHeapFlagBits
$cpeek :: Ptr MemoryHeapFlagBits -> IO MemoryHeapFlagBits
pokeByteOff :: forall b. Ptr b -> Int -> MemoryHeapFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MemoryHeapFlagBits -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO MemoryHeapFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MemoryHeapFlagBits
pokeElemOff :: Ptr MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits -> IO ()
$cpokeElemOff :: Ptr MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits -> IO ()
peekElemOff :: Ptr MemoryHeapFlagBits -> Int -> IO MemoryHeapFlagBits
$cpeekElemOff :: Ptr MemoryHeapFlagBits -> Int -> IO MemoryHeapFlagBits
alignment :: MemoryHeapFlagBits -> Int
$calignment :: MemoryHeapFlagBits -> Int
sizeOf :: MemoryHeapFlagBits -> Int
$csizeOf :: MemoryHeapFlagBits -> Int
Storable, MemoryHeapFlagBits
forall a. a -> Zero a
zero :: MemoryHeapFlagBits
$czero :: MemoryHeapFlagBits
Zero, Eq MemoryHeapFlagBits
MemoryHeapFlagBits
Int -> MemoryHeapFlagBits
MemoryHeapFlagBits -> Bool
MemoryHeapFlagBits -> Int
MemoryHeapFlagBits -> Maybe Int
MemoryHeapFlagBits -> MemoryHeapFlagBits
MemoryHeapFlagBits -> Int -> Bool
MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
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 :: MemoryHeapFlagBits -> Int
$cpopCount :: MemoryHeapFlagBits -> Int
rotateR :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$crotateR :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
rotateL :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$crotateL :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
unsafeShiftR :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$cunsafeShiftR :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
shiftR :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$cshiftR :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
unsafeShiftL :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$cunsafeShiftL :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
shiftL :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$cshiftL :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
isSigned :: MemoryHeapFlagBits -> Bool
$cisSigned :: MemoryHeapFlagBits -> Bool
bitSize :: MemoryHeapFlagBits -> Int
$cbitSize :: MemoryHeapFlagBits -> Int
bitSizeMaybe :: MemoryHeapFlagBits -> Maybe Int
$cbitSizeMaybe :: MemoryHeapFlagBits -> Maybe Int
testBit :: MemoryHeapFlagBits -> Int -> Bool
$ctestBit :: MemoryHeapFlagBits -> Int -> Bool
complementBit :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$ccomplementBit :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
clearBit :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$cclearBit :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
setBit :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$csetBit :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
bit :: Int -> MemoryHeapFlagBits
$cbit :: Int -> MemoryHeapFlagBits
zeroBits :: MemoryHeapFlagBits
$czeroBits :: MemoryHeapFlagBits
rotate :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$crotate :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
shift :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
$cshift :: MemoryHeapFlagBits -> Int -> MemoryHeapFlagBits
complement :: MemoryHeapFlagBits -> MemoryHeapFlagBits
$ccomplement :: MemoryHeapFlagBits -> MemoryHeapFlagBits
xor :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
$cxor :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
.|. :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
$c.|. :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
.&. :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
$c.&. :: MemoryHeapFlagBits -> MemoryHeapFlagBits -> MemoryHeapFlagBits
Bits, Bits MemoryHeapFlagBits
MemoryHeapFlagBits -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: MemoryHeapFlagBits -> Int
$ccountTrailingZeros :: MemoryHeapFlagBits -> Int
countLeadingZeros :: MemoryHeapFlagBits -> Int
$ccountLeadingZeros :: MemoryHeapFlagBits -> Int
finiteBitSize :: MemoryHeapFlagBits -> Int
$cfiniteBitSize :: MemoryHeapFlagBits -> Int
FiniteBits)
pattern $bMEMORY_HEAP_DEVICE_LOCAL_BIT :: MemoryHeapFlagBits
$mMEMORY_HEAP_DEVICE_LOCAL_BIT :: forall {r}. MemoryHeapFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_HEAP_DEVICE_LOCAL_BIT = MemoryHeapFlagBits 0x00000001
pattern $bMEMORY_HEAP_SEU_SAFE_BIT :: MemoryHeapFlagBits
$mMEMORY_HEAP_SEU_SAFE_BIT :: forall {r}. MemoryHeapFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_HEAP_SEU_SAFE_BIT = MemoryHeapFlagBits 0x00000004
pattern $bMEMORY_HEAP_MULTI_INSTANCE_BIT :: MemoryHeapFlagBits
$mMEMORY_HEAP_MULTI_INSTANCE_BIT :: forall {r}. MemoryHeapFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_HEAP_MULTI_INSTANCE_BIT = MemoryHeapFlagBits 0x00000002
conNameMemoryHeapFlagBits :: String
conNameMemoryHeapFlagBits :: String
conNameMemoryHeapFlagBits = String
"MemoryHeapFlagBits"
enumPrefixMemoryHeapFlagBits :: String
enumPrefixMemoryHeapFlagBits :: String
enumPrefixMemoryHeapFlagBits = String
"MEMORY_HEAP_"
showTableMemoryHeapFlagBits :: [(MemoryHeapFlagBits, String)]
showTableMemoryHeapFlagBits :: [(MemoryHeapFlagBits, String)]
showTableMemoryHeapFlagBits =
[
( MemoryHeapFlagBits
MEMORY_HEAP_DEVICE_LOCAL_BIT
, String
"DEVICE_LOCAL_BIT"
)
, (MemoryHeapFlagBits
MEMORY_HEAP_SEU_SAFE_BIT, String
"SEU_SAFE_BIT")
,
( MemoryHeapFlagBits
MEMORY_HEAP_MULTI_INSTANCE_BIT
, String
"MULTI_INSTANCE_BIT"
)
]
instance Show MemoryHeapFlagBits where
showsPrec :: Int -> MemoryHeapFlagBits -> ShowS
showsPrec =
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixMemoryHeapFlagBits
[(MemoryHeapFlagBits, String)]
showTableMemoryHeapFlagBits
String
conNameMemoryHeapFlagBits
(\(MemoryHeapFlagBits 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 MemoryHeapFlagBits where
readPrec :: ReadPrec MemoryHeapFlagBits
readPrec =
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixMemoryHeapFlagBits
[(MemoryHeapFlagBits, String)]
showTableMemoryHeapFlagBits
String
conNameMemoryHeapFlagBits
Flags -> MemoryHeapFlagBits
MemoryHeapFlagBits