{-# language CPP #-}
module Vulkan.Core11.Enums.MemoryAllocateFlagBits ( MemoryAllocateFlagBits( MEMORY_ALLOCATE_DEVICE_MASK_BIT
, MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT
, MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT
, ..
)
, MemoryAllocateFlags
) where
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.Bits (Bits)
import Foreign.Storable (Storable)
import GHC.Read (Read(readPrec))
import Text.Read.Lex (Lexeme(Ident))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Zero (Zero)
newtype MemoryAllocateFlagBits = MemoryAllocateFlagBits Flags
deriving newtype (MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
(MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool)
-> (MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool)
-> Eq MemoryAllocateFlagBits
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
Eq MemoryAllocateFlagBits =>
(MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Ordering)
-> (MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool)
-> (MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool)
-> (MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool)
-> (MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool)
-> (MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits)
-> Ord 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
$cp1Ord :: Eq MemoryAllocateFlagBits
Ord, Ptr b -> Int -> IO MemoryAllocateFlagBits
Ptr b -> Int -> MemoryAllocateFlagBits -> IO ()
Ptr MemoryAllocateFlagBits -> IO MemoryAllocateFlagBits
Ptr MemoryAllocateFlagBits -> Int -> IO MemoryAllocateFlagBits
Ptr MemoryAllocateFlagBits
-> Int -> MemoryAllocateFlagBits -> IO ()
Ptr MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> IO ()
MemoryAllocateFlagBits -> Int
(MemoryAllocateFlagBits -> Int)
-> (MemoryAllocateFlagBits -> Int)
-> (Ptr MemoryAllocateFlagBits -> Int -> IO MemoryAllocateFlagBits)
-> (Ptr MemoryAllocateFlagBits
-> Int -> MemoryAllocateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO MemoryAllocateFlagBits)
-> (forall b. Ptr b -> Int -> MemoryAllocateFlagBits -> IO ())
-> (Ptr MemoryAllocateFlagBits -> IO MemoryAllocateFlagBits)
-> (Ptr MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> IO ())
-> Storable MemoryAllocateFlagBits
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 :: Ptr b -> Int -> MemoryAllocateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MemoryAllocateFlagBits -> IO ()
peekByteOff :: 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
MemoryAllocateFlagBits -> Zero MemoryAllocateFlagBits
forall a. a -> Zero a
zero :: MemoryAllocateFlagBits
$czero :: MemoryAllocateFlagBits
Zero, Eq MemoryAllocateFlagBits
MemoryAllocateFlagBits
Eq MemoryAllocateFlagBits =>
(MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> MemoryAllocateFlagBits
-> (Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> Bool)
-> (MemoryAllocateFlagBits -> Maybe Int)
-> (MemoryAllocateFlagBits -> Int)
-> (MemoryAllocateFlagBits -> Bool)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits)
-> (MemoryAllocateFlagBits -> Int)
-> Bits 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
$cp1Bits :: Eq MemoryAllocateFlagBits
Bits)
pattern $bMEMORY_ALLOCATE_DEVICE_MASK_BIT :: MemoryAllocateFlagBits
$mMEMORY_ALLOCATE_DEVICE_MASK_BIT :: forall r.
MemoryAllocateFlagBits -> (Void# -> r) -> (Void# -> 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 -> (Void# -> r) -> (Void# -> 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 -> (Void# -> r) -> (Void# -> r) -> r
MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT = MemoryAllocateFlagBits 0x00000002
type MemoryAllocateFlags = MemoryAllocateFlagBits
instance Show MemoryAllocateFlagBits where
showsPrec :: Int -> MemoryAllocateFlagBits -> ShowS
showsPrec p :: Int
p = \case
MEMORY_ALLOCATE_DEVICE_MASK_BIT -> String -> ShowS
showString "MEMORY_ALLOCATE_DEVICE_MASK_BIT"
MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT -> String -> ShowS
showString "MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT"
MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT -> String -> ShowS
showString "MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT"
MemoryAllocateFlagBits x :: Flags
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "MemoryAllocateFlagBits 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)
instance Read MemoryAllocateFlagBits where
readPrec :: ReadPrec MemoryAllocateFlagBits
readPrec = ReadPrec MemoryAllocateFlagBits -> ReadPrec MemoryAllocateFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec MemoryAllocateFlagBits)]
-> ReadPrec MemoryAllocateFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("MEMORY_ALLOCATE_DEVICE_MASK_BIT", MemoryAllocateFlagBits -> ReadPrec MemoryAllocateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryAllocateFlagBits
MEMORY_ALLOCATE_DEVICE_MASK_BIT)
, ("MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT", MemoryAllocateFlagBits -> ReadPrec MemoryAllocateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryAllocateFlagBits
MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT)
, ("MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT", MemoryAllocateFlagBits -> ReadPrec MemoryAllocateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryAllocateFlagBits
MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT)]
ReadPrec MemoryAllocateFlagBits
-> ReadPrec MemoryAllocateFlagBits
-> ReadPrec MemoryAllocateFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec MemoryAllocateFlagBits
-> ReadPrec MemoryAllocateFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "MemoryAllocateFlagBits")
Flags
v <- ReadPrec Flags -> ReadPrec Flags
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Flags
forall a. Read a => ReadPrec a
readPrec
MemoryAllocateFlagBits -> ReadPrec MemoryAllocateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> MemoryAllocateFlagBits
MemoryAllocateFlagBits Flags
v)))