{-# language CPP #-}
-- No documentation found for Chapter "MemoryAllocateFlagBits"
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

-- | VkMemoryAllocateFlagBits - Bitmask specifying flags for a device memory
-- allocation
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_1 VK_VERSION_1_1>,
-- 'MemoryAllocateFlags'
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
$c== :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
== :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
$c/= :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
/= :: 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
$ccompare :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Ordering
compare :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Ordering
$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
>= :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> Bool
$cmax :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
max :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$cmin :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
min :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
Ord, 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
$csizeOf :: MemoryAllocateFlagBits -> Int
sizeOf :: MemoryAllocateFlagBits -> Int
$calignment :: MemoryAllocateFlagBits -> Int
alignment :: MemoryAllocateFlagBits -> Int
$cpeekElemOff :: Ptr MemoryAllocateFlagBits -> Int -> IO MemoryAllocateFlagBits
peekElemOff :: Ptr MemoryAllocateFlagBits -> Int -> IO MemoryAllocateFlagBits
$cpokeElemOff :: Ptr MemoryAllocateFlagBits
-> Int -> MemoryAllocateFlagBits -> IO ()
pokeElemOff :: Ptr MemoryAllocateFlagBits
-> Int -> MemoryAllocateFlagBits -> IO ()
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MemoryAllocateFlagBits
peekByteOff :: forall b. Ptr b -> Int -> IO MemoryAllocateFlagBits
$cpokeByteOff :: forall b. Ptr b -> Int -> MemoryAllocateFlagBits -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> MemoryAllocateFlagBits -> IO ()
$cpeek :: Ptr MemoryAllocateFlagBits -> IO MemoryAllocateFlagBits
peek :: Ptr MemoryAllocateFlagBits -> IO MemoryAllocateFlagBits
$cpoke :: Ptr MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> IO ()
poke :: Ptr MemoryAllocateFlagBits -> MemoryAllocateFlagBits -> IO ()
Storable, MemoryAllocateFlagBits
MemoryAllocateFlagBits -> Zero MemoryAllocateFlagBits
forall a. a -> Zero a
$czero :: MemoryAllocateFlagBits
zero :: 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
$c.&. :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
.&. :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$c.|. :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
.|. :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$cxor :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
xor :: MemoryAllocateFlagBits
-> MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$ccomplement :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits
complement :: MemoryAllocateFlagBits -> MemoryAllocateFlagBits
$cshift :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
shift :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$crotate :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
rotate :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$czeroBits :: MemoryAllocateFlagBits
zeroBits :: MemoryAllocateFlagBits
$cbit :: Int -> MemoryAllocateFlagBits
bit :: Int -> MemoryAllocateFlagBits
$csetBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
setBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cclearBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
clearBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$ccomplementBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
complementBit :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$ctestBit :: MemoryAllocateFlagBits -> Int -> Bool
testBit :: MemoryAllocateFlagBits -> Int -> Bool
$cbitSizeMaybe :: MemoryAllocateFlagBits -> Maybe Int
bitSizeMaybe :: MemoryAllocateFlagBits -> Maybe Int
$cbitSize :: MemoryAllocateFlagBits -> Int
bitSize :: MemoryAllocateFlagBits -> Int
$cisSigned :: MemoryAllocateFlagBits -> Bool
isSigned :: MemoryAllocateFlagBits -> Bool
$cshiftL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
shiftL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cunsafeShiftL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
unsafeShiftL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cshiftR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
shiftR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cunsafeShiftR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
unsafeShiftR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$crotateL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
rotateL :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$crotateR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
rotateR :: MemoryAllocateFlagBits -> Int -> MemoryAllocateFlagBits
$cpopCount :: MemoryAllocateFlagBits -> Int
popCount :: MemoryAllocateFlagBits -> Int
Bits, Bits MemoryAllocateFlagBits
Bits MemoryAllocateFlagBits =>
(MemoryAllocateFlagBits -> Int)
-> (MemoryAllocateFlagBits -> Int)
-> (MemoryAllocateFlagBits -> Int)
-> FiniteBits MemoryAllocateFlagBits
MemoryAllocateFlagBits -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: MemoryAllocateFlagBits -> Int
finiteBitSize :: MemoryAllocateFlagBits -> Int
$ccountLeadingZeros :: MemoryAllocateFlagBits -> Int
countLeadingZeros :: MemoryAllocateFlagBits -> Int
$ccountTrailingZeros :: MemoryAllocateFlagBits -> Int
countTrailingZeros :: MemoryAllocateFlagBits -> Int
FiniteBits)

-- | 'MEMORY_ALLOCATE_DEVICE_MASK_BIT' specifies that memory will be
-- allocated for the devices in
-- 'Vulkan.Core11.Promoted_From_VK_KHR_device_group.MemoryAllocateFlagsInfo'::@deviceMask@.
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

-- | 'MEMORY_ALLOCATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT' specifies that the
-- memory’s address /can/ be saved and reused on a subsequent run (e.g. for
-- trace capture and replay), see
-- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.BufferOpaqueCaptureAddressCreateInfo'
-- for more detail.
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

-- | 'MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT' specifies that the memory /can/ be
-- attached to a buffer object created with the
-- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_SHADER_DEVICE_ADDRESS_BIT'
-- bit set in @usage@, and that the memory handle /can/ be used to retrieve
-- an opaque address via
-- 'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.getDeviceMemoryOpaqueCaptureAddress'.
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 =
    String
-> [(MemoryAllocateFlagBits, String)]
-> String
-> (MemoryAllocateFlagBits -> Flags)
-> (Flags -> ShowS)
-> Int
-> MemoryAllocateFlagBits
-> ShowS
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" 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 MemoryAllocateFlagBits where
  readPrec :: ReadPrec MemoryAllocateFlagBits
readPrec =
    String
-> [(MemoryAllocateFlagBits, String)]
-> String
-> (Flags -> MemoryAllocateFlagBits)
-> ReadPrec MemoryAllocateFlagBits
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixMemoryAllocateFlagBits
      [(MemoryAllocateFlagBits, String)]
showTableMemoryAllocateFlagBits
      String
conNameMemoryAllocateFlagBits
      Flags -> MemoryAllocateFlagBits
MemoryAllocateFlagBits