{-# language CPP #-}
module Vulkan.Extensions.VK_NV_dedicated_allocation ( DedicatedAllocationImageCreateInfoNV(..)
, DedicatedAllocationBufferCreateInfoNV(..)
, DedicatedAllocationMemoryAllocateInfoNV(..)
, NV_DEDICATED_ALLOCATION_SPEC_VERSION
, pattern NV_DEDICATED_ALLOCATION_SPEC_VERSION
, NV_DEDICATED_ALLOCATION_EXTENSION_NAME
, pattern NV_DEDICATED_ALLOCATION_EXTENSION_NAME
) where
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Data.String (IsString)
import Data.Typeable (Typeable)
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.Core10.Handles (Buffer)
import Vulkan.Core10.Handles (Image)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEDICATED_ALLOCATION_BUFFER_CREATE_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEDICATED_ALLOCATION_IMAGE_CREATE_INFO_NV))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEDICATED_ALLOCATION_MEMORY_ALLOCATE_INFO_NV))
data DedicatedAllocationImageCreateInfoNV = DedicatedAllocationImageCreateInfoNV
{
DedicatedAllocationImageCreateInfoNV -> Bool
dedicatedAllocation :: Bool }
deriving (Typeable, DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
$c/= :: DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
== :: DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
$c== :: DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DedicatedAllocationImageCreateInfoNV)
#endif
deriving instance Show DedicatedAllocationImageCreateInfoNV
instance ToCStruct DedicatedAllocationImageCreateInfoNV where
withCStruct :: forall b.
DedicatedAllocationImageCreateInfoNV
-> (Ptr DedicatedAllocationImageCreateInfoNV -> IO b) -> IO b
withCStruct DedicatedAllocationImageCreateInfoNV
x Ptr DedicatedAllocationImageCreateInfoNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr DedicatedAllocationImageCreateInfoNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationImageCreateInfoNV
p DedicatedAllocationImageCreateInfoNV
x (Ptr DedicatedAllocationImageCreateInfoNV -> IO b
f Ptr DedicatedAllocationImageCreateInfoNV
p)
pokeCStruct :: forall b.
Ptr DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationImageCreateInfoNV
p DedicatedAllocationImageCreateInfoNV{Bool
dedicatedAllocation :: Bool
$sel:dedicatedAllocation:DedicatedAllocationImageCreateInfoNV :: DedicatedAllocationImageCreateInfoNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_IMAGE_CREATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
dedicatedAllocation))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr DedicatedAllocationImageCreateInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr DedicatedAllocationImageCreateInfoNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_IMAGE_CREATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct DedicatedAllocationImageCreateInfoNV where
peekCStruct :: Ptr DedicatedAllocationImageCreateInfoNV
-> IO DedicatedAllocationImageCreateInfoNV
peekCStruct Ptr DedicatedAllocationImageCreateInfoNV
p = do
Bool32
dedicatedAllocation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr DedicatedAllocationImageCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> DedicatedAllocationImageCreateInfoNV
DedicatedAllocationImageCreateInfoNV
(Bool32 -> Bool
bool32ToBool Bool32
dedicatedAllocation)
instance Storable DedicatedAllocationImageCreateInfoNV where
sizeOf :: DedicatedAllocationImageCreateInfoNV -> Int
sizeOf ~DedicatedAllocationImageCreateInfoNV
_ = Int
24
alignment :: DedicatedAllocationImageCreateInfoNV -> Int
alignment ~DedicatedAllocationImageCreateInfoNV
_ = Int
8
peek :: Ptr DedicatedAllocationImageCreateInfoNV
-> IO DedicatedAllocationImageCreateInfoNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DedicatedAllocationImageCreateInfoNV
-> DedicatedAllocationImageCreateInfoNV -> IO ()
poke Ptr DedicatedAllocationImageCreateInfoNV
ptr DedicatedAllocationImageCreateInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationImageCreateInfoNV
ptr DedicatedAllocationImageCreateInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DedicatedAllocationImageCreateInfoNV where
zero :: DedicatedAllocationImageCreateInfoNV
zero = Bool -> DedicatedAllocationImageCreateInfoNV
DedicatedAllocationImageCreateInfoNV
forall a. Zero a => a
zero
data DedicatedAllocationBufferCreateInfoNV = DedicatedAllocationBufferCreateInfoNV
{
DedicatedAllocationBufferCreateInfoNV -> Bool
dedicatedAllocation :: Bool }
deriving (Typeable, DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
$c/= :: DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
== :: DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
$c== :: DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DedicatedAllocationBufferCreateInfoNV)
#endif
deriving instance Show DedicatedAllocationBufferCreateInfoNV
instance ToCStruct DedicatedAllocationBufferCreateInfoNV where
withCStruct :: forall b.
DedicatedAllocationBufferCreateInfoNV
-> (Ptr DedicatedAllocationBufferCreateInfoNV -> IO b) -> IO b
withCStruct DedicatedAllocationBufferCreateInfoNV
x Ptr DedicatedAllocationBufferCreateInfoNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 forall a b. (a -> b) -> a -> b
$ \Ptr DedicatedAllocationBufferCreateInfoNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationBufferCreateInfoNV
p DedicatedAllocationBufferCreateInfoNV
x (Ptr DedicatedAllocationBufferCreateInfoNV -> IO b
f Ptr DedicatedAllocationBufferCreateInfoNV
p)
pokeCStruct :: forall b.
Ptr DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationBufferCreateInfoNV
p DedicatedAllocationBufferCreateInfoNV{Bool
dedicatedAllocation :: Bool
$sel:dedicatedAllocation:DedicatedAllocationBufferCreateInfoNV :: DedicatedAllocationBufferCreateInfoNV -> Bool
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_BUFFER_CREATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
dedicatedAllocation))
IO b
f
cStructSize :: Int
cStructSize = Int
24
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b. Ptr DedicatedAllocationBufferCreateInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr DedicatedAllocationBufferCreateInfoNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_BUFFER_CREATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationBufferCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (forall a. Zero a => a
zero))
IO b
f
instance FromCStruct DedicatedAllocationBufferCreateInfoNV where
peekCStruct :: Ptr DedicatedAllocationBufferCreateInfoNV
-> IO DedicatedAllocationBufferCreateInfoNV
peekCStruct Ptr DedicatedAllocationBufferCreateInfoNV
p = do
Bool32
dedicatedAllocation <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr DedicatedAllocationBufferCreateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Bool -> DedicatedAllocationBufferCreateInfoNV
DedicatedAllocationBufferCreateInfoNV
(Bool32 -> Bool
bool32ToBool Bool32
dedicatedAllocation)
instance Storable DedicatedAllocationBufferCreateInfoNV where
sizeOf :: DedicatedAllocationBufferCreateInfoNV -> Int
sizeOf ~DedicatedAllocationBufferCreateInfoNV
_ = Int
24
alignment :: DedicatedAllocationBufferCreateInfoNV -> Int
alignment ~DedicatedAllocationBufferCreateInfoNV
_ = Int
8
peek :: Ptr DedicatedAllocationBufferCreateInfoNV
-> IO DedicatedAllocationBufferCreateInfoNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DedicatedAllocationBufferCreateInfoNV
-> DedicatedAllocationBufferCreateInfoNV -> IO ()
poke Ptr DedicatedAllocationBufferCreateInfoNV
ptr DedicatedAllocationBufferCreateInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationBufferCreateInfoNV
ptr DedicatedAllocationBufferCreateInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DedicatedAllocationBufferCreateInfoNV where
zero :: DedicatedAllocationBufferCreateInfoNV
zero = Bool -> DedicatedAllocationBufferCreateInfoNV
DedicatedAllocationBufferCreateInfoNV
forall a. Zero a => a
zero
data DedicatedAllocationMemoryAllocateInfoNV = DedicatedAllocationMemoryAllocateInfoNV
{
DedicatedAllocationMemoryAllocateInfoNV -> Image
image :: Image
,
DedicatedAllocationMemoryAllocateInfoNV -> Buffer
buffer :: Buffer
}
deriving (Typeable, DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
$c/= :: DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
== :: DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
$c== :: DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DedicatedAllocationMemoryAllocateInfoNV)
#endif
deriving instance Show DedicatedAllocationMemoryAllocateInfoNV
instance ToCStruct DedicatedAllocationMemoryAllocateInfoNV where
withCStruct :: forall b.
DedicatedAllocationMemoryAllocateInfoNV
-> (Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b) -> IO b
withCStruct DedicatedAllocationMemoryAllocateInfoNV
x Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 forall a b. (a -> b) -> a -> b
$ \Ptr DedicatedAllocationMemoryAllocateInfoNV
p -> forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationMemoryAllocateInfoNV
p DedicatedAllocationMemoryAllocateInfoNV
x (Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b
f Ptr DedicatedAllocationMemoryAllocateInfoNV
p)
pokeCStruct :: forall b.
Ptr DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationMemoryAllocateInfoNV
p DedicatedAllocationMemoryAllocateInfoNV{Image
Buffer
buffer :: Buffer
image :: Image
$sel:buffer:DedicatedAllocationMemoryAllocateInfoNV :: DedicatedAllocationMemoryAllocateInfoNV -> Buffer
$sel:image:DedicatedAllocationMemoryAllocateInfoNV :: DedicatedAllocationMemoryAllocateInfoNV -> Image
..} IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_MEMORY_ALLOCATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Image)) (Image
image)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Buffer)) (Buffer
buffer)
IO b
f
cStructSize :: Int
cStructSize = Int
32
cStructAlignment :: Int
cStructAlignment = Int
8
pokeZeroCStruct :: forall b.
Ptr DedicatedAllocationMemoryAllocateInfoNV -> IO b -> IO b
pokeZeroCStruct Ptr DedicatedAllocationMemoryAllocateInfoNV
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEDICATED_ALLOCATION_MEMORY_ALLOCATE_INFO_NV)
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
IO b
f
instance FromCStruct DedicatedAllocationMemoryAllocateInfoNV where
peekCStruct :: Ptr DedicatedAllocationMemoryAllocateInfoNV
-> IO DedicatedAllocationMemoryAllocateInfoNV
peekCStruct Ptr DedicatedAllocationMemoryAllocateInfoNV
p = do
Image
image <- forall a. Storable a => Ptr a -> IO a
peek @Image ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Image))
Buffer
buffer <- forall a. Storable a => Ptr a -> IO a
peek @Buffer ((Ptr DedicatedAllocationMemoryAllocateInfoNV
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Buffer))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Image -> Buffer -> DedicatedAllocationMemoryAllocateInfoNV
DedicatedAllocationMemoryAllocateInfoNV
Image
image Buffer
buffer
instance Storable DedicatedAllocationMemoryAllocateInfoNV where
sizeOf :: DedicatedAllocationMemoryAllocateInfoNV -> Int
sizeOf ~DedicatedAllocationMemoryAllocateInfoNV
_ = Int
32
alignment :: DedicatedAllocationMemoryAllocateInfoNV -> Int
alignment ~DedicatedAllocationMemoryAllocateInfoNV
_ = Int
8
peek :: Ptr DedicatedAllocationMemoryAllocateInfoNV
-> IO DedicatedAllocationMemoryAllocateInfoNV
peek = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DedicatedAllocationMemoryAllocateInfoNV
-> DedicatedAllocationMemoryAllocateInfoNV -> IO ()
poke Ptr DedicatedAllocationMemoryAllocateInfoNV
ptr DedicatedAllocationMemoryAllocateInfoNV
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DedicatedAllocationMemoryAllocateInfoNV
ptr DedicatedAllocationMemoryAllocateInfoNV
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DedicatedAllocationMemoryAllocateInfoNV where
zero :: DedicatedAllocationMemoryAllocateInfoNV
zero = Image -> Buffer -> DedicatedAllocationMemoryAllocateInfoNV
DedicatedAllocationMemoryAllocateInfoNV
forall a. Zero a => a
zero
forall a. Zero a => a
zero
type NV_DEDICATED_ALLOCATION_SPEC_VERSION = 1
pattern NV_DEDICATED_ALLOCATION_SPEC_VERSION :: forall a . Integral a => a
pattern $bNV_DEDICATED_ALLOCATION_SPEC_VERSION :: forall a. Integral a => a
$mNV_DEDICATED_ALLOCATION_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DEDICATED_ALLOCATION_SPEC_VERSION = 1
type NV_DEDICATED_ALLOCATION_EXTENSION_NAME = "VK_NV_dedicated_allocation"
pattern NV_DEDICATED_ALLOCATION_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bNV_DEDICATED_ALLOCATION_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mNV_DEDICATED_ALLOCATION_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> ((# #) -> r) -> ((# #) -> r) -> r
NV_DEDICATED_ALLOCATION_EXTENSION_NAME = "VK_NV_dedicated_allocation"