{-# language CPP #-}
module Vulkan.Core10.Enums.MemoryPropertyFlagBits ( MemoryPropertyFlags
, MemoryPropertyFlagBits( MEMORY_PROPERTY_DEVICE_LOCAL_BIT
, MEMORY_PROPERTY_HOST_VISIBLE_BIT
, MEMORY_PROPERTY_HOST_COHERENT_BIT
, MEMORY_PROPERTY_HOST_CACHED_BIT
, MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT
, MEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV
, MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
, MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
, MEMORY_PROPERTY_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 MemoryPropertyFlags = MemoryPropertyFlagBits
newtype MemoryPropertyFlagBits = MemoryPropertyFlagBits Flags
deriving newtype (MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
(MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool)
-> (MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool)
-> Eq MemoryPropertyFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
== :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
$c/= :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
/= :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
Eq, Eq MemoryPropertyFlagBits
Eq MemoryPropertyFlagBits =>
(MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Ordering)
-> (MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool)
-> (MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool)
-> (MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool)
-> (MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool)
-> (MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits)
-> Ord MemoryPropertyFlagBits
MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Ordering
MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
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 :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Ordering
compare :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Ordering
$c< :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
< :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
$c<= :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
<= :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
$c> :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
> :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
$c>= :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
>= :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> Bool
$cmax :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
max :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
$cmin :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
min :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
Ord, Ptr MemoryPropertyFlagBits -> IO MemoryPropertyFlagBits
Ptr MemoryPropertyFlagBits -> Int -> IO MemoryPropertyFlagBits
Ptr MemoryPropertyFlagBits
-> Int -> MemoryPropertyFlagBits -> IO ()
Ptr MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> IO ()
MemoryPropertyFlagBits -> Int
(MemoryPropertyFlagBits -> Int)
-> (MemoryPropertyFlagBits -> Int)
-> (Ptr MemoryPropertyFlagBits -> Int -> IO MemoryPropertyFlagBits)
-> (Ptr MemoryPropertyFlagBits
-> Int -> MemoryPropertyFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO MemoryPropertyFlagBits)
-> (forall b. Ptr b -> Int -> MemoryPropertyFlagBits -> IO ())
-> (Ptr MemoryPropertyFlagBits -> IO MemoryPropertyFlagBits)
-> (Ptr MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> IO ())
-> Storable MemoryPropertyFlagBits
forall b. Ptr b -> Int -> IO MemoryPropertyFlagBits
forall b. Ptr b -> Int -> MemoryPropertyFlagBits -> 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 :: MemoryPropertyFlagBits -> Int
sizeOf :: MemoryPropertyFlagBits -> Int
$calignment :: MemoryPropertyFlagBits -> Int
alignment :: MemoryPropertyFlagBits -> Int
$cpeekElemOff :: Ptr MemoryPropertyFlagBits -> Int -> IO MemoryPropertyFlagBits
peekElemOff :: Ptr MemoryPropertyFlagBits -> Int -> IO MemoryPropertyFlagBits
$cpokeElemOff :: Ptr MemoryPropertyFlagBits
-> Int -> MemoryPropertyFlagBits -> IO ()
pokeElemOff :: Ptr MemoryPropertyFlagBits
-> Int -> MemoryPropertyFlagBits -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MemoryPropertyFlagBits
peekByteOff :: forall b. Ptr b -> Int -> IO MemoryPropertyFlagBits
$cpokeByteOff :: forall b. Ptr b -> Int -> MemoryPropertyFlagBits -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> MemoryPropertyFlagBits -> IO ()
$cpeek :: Ptr MemoryPropertyFlagBits -> IO MemoryPropertyFlagBits
peek :: Ptr MemoryPropertyFlagBits -> IO MemoryPropertyFlagBits
$cpoke :: Ptr MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> IO ()
poke :: Ptr MemoryPropertyFlagBits -> MemoryPropertyFlagBits -> IO ()
Storable, MemoryPropertyFlagBits
MemoryPropertyFlagBits -> Zero MemoryPropertyFlagBits
forall a. a -> Zero a
$czero :: MemoryPropertyFlagBits
zero :: MemoryPropertyFlagBits
Zero, Eq MemoryPropertyFlagBits
MemoryPropertyFlagBits
Eq MemoryPropertyFlagBits =>
(MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> MemoryPropertyFlagBits
-> (Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> Bool)
-> (MemoryPropertyFlagBits -> Maybe Int)
-> (MemoryPropertyFlagBits -> Int)
-> (MemoryPropertyFlagBits -> Bool)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits)
-> (MemoryPropertyFlagBits -> Int)
-> Bits MemoryPropertyFlagBits
Int -> MemoryPropertyFlagBits
MemoryPropertyFlagBits -> Bool
MemoryPropertyFlagBits -> Int
MemoryPropertyFlagBits -> Maybe Int
MemoryPropertyFlagBits -> MemoryPropertyFlagBits
MemoryPropertyFlagBits -> Int -> Bool
MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
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.&. :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
.&. :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
$c.|. :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
.|. :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
$cxor :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
xor :: MemoryPropertyFlagBits
-> MemoryPropertyFlagBits -> MemoryPropertyFlagBits
$ccomplement :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits
complement :: MemoryPropertyFlagBits -> MemoryPropertyFlagBits
$cshift :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
shift :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$crotate :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
rotate :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$czeroBits :: MemoryPropertyFlagBits
zeroBits :: MemoryPropertyFlagBits
$cbit :: Int -> MemoryPropertyFlagBits
bit :: Int -> MemoryPropertyFlagBits
$csetBit :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
setBit :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$cclearBit :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
clearBit :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$ccomplementBit :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
complementBit :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$ctestBit :: MemoryPropertyFlagBits -> Int -> Bool
testBit :: MemoryPropertyFlagBits -> Int -> Bool
$cbitSizeMaybe :: MemoryPropertyFlagBits -> Maybe Int
bitSizeMaybe :: MemoryPropertyFlagBits -> Maybe Int
$cbitSize :: MemoryPropertyFlagBits -> Int
bitSize :: MemoryPropertyFlagBits -> Int
$cisSigned :: MemoryPropertyFlagBits -> Bool
isSigned :: MemoryPropertyFlagBits -> Bool
$cshiftL :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
shiftL :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$cunsafeShiftL :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
unsafeShiftL :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$cshiftR :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
shiftR :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$cunsafeShiftR :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
unsafeShiftR :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$crotateL :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
rotateL :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$crotateR :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
rotateR :: MemoryPropertyFlagBits -> Int -> MemoryPropertyFlagBits
$cpopCount :: MemoryPropertyFlagBits -> Int
popCount :: MemoryPropertyFlagBits -> Int
Bits, Bits MemoryPropertyFlagBits
Bits MemoryPropertyFlagBits =>
(MemoryPropertyFlagBits -> Int)
-> (MemoryPropertyFlagBits -> Int)
-> (MemoryPropertyFlagBits -> Int)
-> FiniteBits MemoryPropertyFlagBits
MemoryPropertyFlagBits -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: MemoryPropertyFlagBits -> Int
finiteBitSize :: MemoryPropertyFlagBits -> Int
$ccountLeadingZeros :: MemoryPropertyFlagBits -> Int
countLeadingZeros :: MemoryPropertyFlagBits -> Int
$ccountTrailingZeros :: MemoryPropertyFlagBits -> Int
countTrailingZeros :: MemoryPropertyFlagBits -> Int
FiniteBits)
pattern $bMEMORY_PROPERTY_DEVICE_LOCAL_BIT :: MemoryPropertyFlagBits
$mMEMORY_PROPERTY_DEVICE_LOCAL_BIT :: forall {r}.
MemoryPropertyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_PROPERTY_DEVICE_LOCAL_BIT = MemoryPropertyFlagBits 0x00000001
pattern $bMEMORY_PROPERTY_HOST_VISIBLE_BIT :: MemoryPropertyFlagBits
$mMEMORY_PROPERTY_HOST_VISIBLE_BIT :: forall {r}.
MemoryPropertyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_PROPERTY_HOST_VISIBLE_BIT = MemoryPropertyFlagBits 0x00000002
pattern $bMEMORY_PROPERTY_HOST_COHERENT_BIT :: MemoryPropertyFlagBits
$mMEMORY_PROPERTY_HOST_COHERENT_BIT :: forall {r}.
MemoryPropertyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_PROPERTY_HOST_COHERENT_BIT = MemoryPropertyFlagBits 0x00000004
pattern $bMEMORY_PROPERTY_HOST_CACHED_BIT :: MemoryPropertyFlagBits
$mMEMORY_PROPERTY_HOST_CACHED_BIT :: forall {r}.
MemoryPropertyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_PROPERTY_HOST_CACHED_BIT = MemoryPropertyFlagBits 0x00000008
pattern $bMEMORY_PROPERTY_LAZILY_ALLOCATED_BIT :: MemoryPropertyFlagBits
$mMEMORY_PROPERTY_LAZILY_ALLOCATED_BIT :: forall {r}.
MemoryPropertyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT = MemoryPropertyFlagBits 0x00000010
pattern $bMEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV :: MemoryPropertyFlagBits
$mMEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV :: forall {r}.
MemoryPropertyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV = MemoryPropertyFlagBits 0x00000100
pattern $bMEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD :: MemoryPropertyFlagBits
$mMEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD :: forall {r}.
MemoryPropertyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD = MemoryPropertyFlagBits 0x00000080
pattern $bMEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD :: MemoryPropertyFlagBits
$mMEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD :: forall {r}.
MemoryPropertyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD = MemoryPropertyFlagBits 0x00000040
pattern $bMEMORY_PROPERTY_PROTECTED_BIT :: MemoryPropertyFlagBits
$mMEMORY_PROPERTY_PROTECTED_BIT :: forall {r}.
MemoryPropertyFlagBits -> ((# #) -> r) -> ((# #) -> r) -> r
MEMORY_PROPERTY_PROTECTED_BIT = MemoryPropertyFlagBits 0x00000020
conNameMemoryPropertyFlagBits :: String
conNameMemoryPropertyFlagBits :: String
conNameMemoryPropertyFlagBits = String
"MemoryPropertyFlagBits"
enumPrefixMemoryPropertyFlagBits :: String
enumPrefixMemoryPropertyFlagBits :: String
enumPrefixMemoryPropertyFlagBits = String
"MEMORY_PROPERTY_"
showTableMemoryPropertyFlagBits :: [(MemoryPropertyFlagBits, String)]
showTableMemoryPropertyFlagBits :: [(MemoryPropertyFlagBits, String)]
showTableMemoryPropertyFlagBits =
[
( MemoryPropertyFlagBits
MEMORY_PROPERTY_DEVICE_LOCAL_BIT
, String
"DEVICE_LOCAL_BIT"
)
,
( MemoryPropertyFlagBits
MEMORY_PROPERTY_HOST_VISIBLE_BIT
, String
"HOST_VISIBLE_BIT"
)
,
( MemoryPropertyFlagBits
MEMORY_PROPERTY_HOST_COHERENT_BIT
, String
"HOST_COHERENT_BIT"
)
,
( MemoryPropertyFlagBits
MEMORY_PROPERTY_HOST_CACHED_BIT
, String
"HOST_CACHED_BIT"
)
,
( MemoryPropertyFlagBits
MEMORY_PROPERTY_LAZILY_ALLOCATED_BIT
, String
"LAZILY_ALLOCATED_BIT"
)
,
( MemoryPropertyFlagBits
MEMORY_PROPERTY_RDMA_CAPABLE_BIT_NV
, String
"RDMA_CAPABLE_BIT_NV"
)
,
( MemoryPropertyFlagBits
MEMORY_PROPERTY_DEVICE_UNCACHED_BIT_AMD
, String
"DEVICE_UNCACHED_BIT_AMD"
)
,
( MemoryPropertyFlagBits
MEMORY_PROPERTY_DEVICE_COHERENT_BIT_AMD
, String
"DEVICE_COHERENT_BIT_AMD"
)
,
( MemoryPropertyFlagBits
MEMORY_PROPERTY_PROTECTED_BIT
, String
"PROTECTED_BIT"
)
]
instance Show MemoryPropertyFlagBits where
showsPrec :: Int -> MemoryPropertyFlagBits -> ShowS
showsPrec =
String
-> [(MemoryPropertyFlagBits, String)]
-> String
-> (MemoryPropertyFlagBits -> Flags)
-> (Flags -> ShowS)
-> Int
-> MemoryPropertyFlagBits
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
String
enumPrefixMemoryPropertyFlagBits
[(MemoryPropertyFlagBits, String)]
showTableMemoryPropertyFlagBits
String
conNameMemoryPropertyFlagBits
(\(MemoryPropertyFlagBits 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 MemoryPropertyFlagBits where
readPrec :: ReadPrec MemoryPropertyFlagBits
readPrec =
String
-> [(MemoryPropertyFlagBits, String)]
-> String
-> (Flags -> MemoryPropertyFlagBits)
-> ReadPrec MemoryPropertyFlagBits
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
String
enumPrefixMemoryPropertyFlagBits
[(MemoryPropertyFlagBits, String)]
showTableMemoryPropertyFlagBits
String
conNameMemoryPropertyFlagBits
Flags -> MemoryPropertyFlagBits
MemoryPropertyFlagBits