{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_memory_priority  ( PhysicalDeviceMemoryPriorityFeaturesEXT(..)
                                                 , MemoryPriorityAllocateInfoEXT(..)
                                                 , EXT_MEMORY_PRIORITY_SPEC_VERSION
                                                 , pattern EXT_MEMORY_PRIORITY_SPEC_VERSION
                                                 , EXT_MEMORY_PRIORITY_EXTENSION_NAME
                                                 , pattern EXT_MEMORY_PRIORITY_EXTENSION_NAME
                                                 ) where

import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(CFloat))
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_PRIORITY_ALLOCATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PRIORITY_FEATURES_EXT))
-- | VkPhysicalDeviceMemoryPriorityFeaturesEXT - Structure describing memory
-- priority features that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceMemoryPriorityFeaturesEXT' structure
-- describe the following features:
--
-- = Description
--
-- If the 'PhysicalDeviceMemoryPriorityFeaturesEXT' structure is included
-- in the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether the feature is supported.
-- 'PhysicalDeviceMemoryPriorityFeaturesEXT' /can/ also be included in the
-- @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable
-- features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceMemoryPriorityFeaturesEXT = PhysicalDeviceMemoryPriorityFeaturesEXT
  { -- | @memoryPriority@ indicates that the implementation supports memory
    -- priorities specified at memory allocation time via
    -- 'MemoryPriorityAllocateInfoEXT'.
    PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
memoryPriority :: Bool }
  deriving (Typeable, PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
(PhysicalDeviceMemoryPriorityFeaturesEXT
 -> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool)
-> (PhysicalDeviceMemoryPriorityFeaturesEXT
    -> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool)
-> Eq PhysicalDeviceMemoryPriorityFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
$c/= :: PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
== :: PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
$c== :: PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMemoryPriorityFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceMemoryPriorityFeaturesEXT

instance ToCStruct PhysicalDeviceMemoryPriorityFeaturesEXT where
  withCStruct :: PhysicalDeviceMemoryPriorityFeaturesEXT
-> (Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b) -> IO b
withCStruct x :: PhysicalDeviceMemoryPriorityFeaturesEXT
x f :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p -> Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p PhysicalDeviceMemoryPriorityFeaturesEXT
x (Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b
f Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p PhysicalDeviceMemoryPriorityFeaturesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PRIORITY_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
memoryPriority))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_PRIORITY_FEATURES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceMemoryPriorityFeaturesEXT where
  peekCStruct :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> IO PhysicalDeviceMemoryPriorityFeaturesEXT
peekCStruct p :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p = do
    Bool32
memoryPriority <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
p Ptr PhysicalDeviceMemoryPriorityFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    PhysicalDeviceMemoryPriorityFeaturesEXT
-> IO PhysicalDeviceMemoryPriorityFeaturesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMemoryPriorityFeaturesEXT
 -> IO PhysicalDeviceMemoryPriorityFeaturesEXT)
-> PhysicalDeviceMemoryPriorityFeaturesEXT
-> IO PhysicalDeviceMemoryPriorityFeaturesEXT
forall a b. (a -> b) -> a -> b
$ Bool -> PhysicalDeviceMemoryPriorityFeaturesEXT
PhysicalDeviceMemoryPriorityFeaturesEXT
             (Bool32 -> Bool
bool32ToBool Bool32
memoryPriority)

instance Storable PhysicalDeviceMemoryPriorityFeaturesEXT where
  sizeOf :: PhysicalDeviceMemoryPriorityFeaturesEXT -> Int
sizeOf ~PhysicalDeviceMemoryPriorityFeaturesEXT
_ = 24
  alignment :: PhysicalDeviceMemoryPriorityFeaturesEXT -> Int
alignment ~PhysicalDeviceMemoryPriorityFeaturesEXT
_ = 8
  peek :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> IO PhysicalDeviceMemoryPriorityFeaturesEXT
peek = Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> IO PhysicalDeviceMemoryPriorityFeaturesEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> IO ()
poke ptr :: Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
ptr poked :: PhysicalDeviceMemoryPriorityFeaturesEXT
poked = Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
-> PhysicalDeviceMemoryPriorityFeaturesEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMemoryPriorityFeaturesEXT
ptr PhysicalDeviceMemoryPriorityFeaturesEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero PhysicalDeviceMemoryPriorityFeaturesEXT where
  zero :: PhysicalDeviceMemoryPriorityFeaturesEXT
zero = Bool -> PhysicalDeviceMemoryPriorityFeaturesEXT
PhysicalDeviceMemoryPriorityFeaturesEXT
           Bool
forall a. Zero a => a
zero


-- | VkMemoryPriorityAllocateInfoEXT - Specify a memory allocation priority
--
-- = Description
--
-- Memory allocations with higher priority /may/ be more likely to stay in
-- device-local memory when the system is under memory pressure.
--
-- If this structure is not included, it is as if the @priority@ value were
-- @0.5@.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data MemoryPriorityAllocateInfoEXT = MemoryPriorityAllocateInfoEXT
  { -- | @priority@ is a floating-point value between @0@ and @1@, indicating the
    -- priority of the allocation relative to other memory allocations. Larger
    -- values are higher priority. The granularity of the priorities is
    -- implementation-dependent.
    --
    -- @priority@ /must/ be between @0@ and @1@, inclusive
    MemoryPriorityAllocateInfoEXT -> Float
priority :: Float }
  deriving (Typeable, MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
(MemoryPriorityAllocateInfoEXT
 -> MemoryPriorityAllocateInfoEXT -> Bool)
-> (MemoryPriorityAllocateInfoEXT
    -> MemoryPriorityAllocateInfoEXT -> Bool)
-> Eq MemoryPriorityAllocateInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
$c/= :: MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
== :: MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
$c== :: MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MemoryPriorityAllocateInfoEXT)
#endif
deriving instance Show MemoryPriorityAllocateInfoEXT

instance ToCStruct MemoryPriorityAllocateInfoEXT where
  withCStruct :: MemoryPriorityAllocateInfoEXT
-> (Ptr MemoryPriorityAllocateInfoEXT -> IO b) -> IO b
withCStruct x :: MemoryPriorityAllocateInfoEXT
x f :: Ptr MemoryPriorityAllocateInfoEXT -> IO b
f = Int -> Int -> (Ptr MemoryPriorityAllocateInfoEXT -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr MemoryPriorityAllocateInfoEXT -> IO b) -> IO b)
-> (Ptr MemoryPriorityAllocateInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr MemoryPriorityAllocateInfoEXT
p -> Ptr MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryPriorityAllocateInfoEXT
p MemoryPriorityAllocateInfoEXT
x (Ptr MemoryPriorityAllocateInfoEXT -> IO b
f Ptr MemoryPriorityAllocateInfoEXT
p)
  pokeCStruct :: Ptr MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> IO b -> IO b
pokeCStruct p :: Ptr MemoryPriorityAllocateInfoEXT
p MemoryPriorityAllocateInfoEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
p Ptr MemoryPriorityAllocateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_PRIORITY_ALLOCATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
p Ptr MemoryPriorityAllocateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
p Ptr MemoryPriorityAllocateInfoEXT -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
priority))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr MemoryPriorityAllocateInfoEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr MemoryPriorityAllocateInfoEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
p Ptr MemoryPriorityAllocateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_PRIORITY_ALLOCATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
p Ptr MemoryPriorityAllocateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MemoryPriorityAllocateInfoEXT
p Ptr MemoryPriorityAllocateInfoEXT -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct MemoryPriorityAllocateInfoEXT where
  peekCStruct :: Ptr MemoryPriorityAllocateInfoEXT
-> IO MemoryPriorityAllocateInfoEXT
peekCStruct p :: Ptr MemoryPriorityAllocateInfoEXT
p = do
    CFloat
priority <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr MemoryPriorityAllocateInfoEXT
p Ptr MemoryPriorityAllocateInfoEXT -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CFloat))
    MemoryPriorityAllocateInfoEXT -> IO MemoryPriorityAllocateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryPriorityAllocateInfoEXT -> IO MemoryPriorityAllocateInfoEXT)
-> MemoryPriorityAllocateInfoEXT
-> IO MemoryPriorityAllocateInfoEXT
forall a b. (a -> b) -> a -> b
$ Float -> MemoryPriorityAllocateInfoEXT
MemoryPriorityAllocateInfoEXT
             ((\(CFloat a :: Float
a) -> Float
a) CFloat
priority)

instance Storable MemoryPriorityAllocateInfoEXT where
  sizeOf :: MemoryPriorityAllocateInfoEXT -> Int
sizeOf ~MemoryPriorityAllocateInfoEXT
_ = 24
  alignment :: MemoryPriorityAllocateInfoEXT -> Int
alignment ~MemoryPriorityAllocateInfoEXT
_ = 8
  peek :: Ptr MemoryPriorityAllocateInfoEXT
-> IO MemoryPriorityAllocateInfoEXT
peek = Ptr MemoryPriorityAllocateInfoEXT
-> IO MemoryPriorityAllocateInfoEXT
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
  poke :: Ptr MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> IO ()
poke ptr :: Ptr MemoryPriorityAllocateInfoEXT
ptr poked :: MemoryPriorityAllocateInfoEXT
poked = Ptr MemoryPriorityAllocateInfoEXT
-> MemoryPriorityAllocateInfoEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MemoryPriorityAllocateInfoEXT
ptr MemoryPriorityAllocateInfoEXT
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())

instance Zero MemoryPriorityAllocateInfoEXT where
  zero :: MemoryPriorityAllocateInfoEXT
zero = Float -> MemoryPriorityAllocateInfoEXT
MemoryPriorityAllocateInfoEXT
           Float
forall a. Zero a => a
zero


type EXT_MEMORY_PRIORITY_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_MEMORY_PRIORITY_SPEC_VERSION"
pattern EXT_MEMORY_PRIORITY_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_MEMORY_PRIORITY_SPEC_VERSION :: a
$mEXT_MEMORY_PRIORITY_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_MEMORY_PRIORITY_SPEC_VERSION = 1


type EXT_MEMORY_PRIORITY_EXTENSION_NAME = "VK_EXT_memory_priority"

-- No documentation found for TopLevel "VK_EXT_MEMORY_PRIORITY_EXTENSION_NAME"
pattern EXT_MEMORY_PRIORITY_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_MEMORY_PRIORITY_EXTENSION_NAME :: a
$mEXT_MEMORY_PRIORITY_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_MEMORY_PRIORITY_EXTENSION_NAME = "VK_EXT_memory_priority"