{-# language CPP #-}
module Vulkan.Extensions.VK_EXT_memory_budget  ( PhysicalDeviceMemoryBudgetPropertiesEXT(..)
                                               , EXT_MEMORY_BUDGET_SPEC_VERSION
                                               , pattern EXT_MEMORY_BUDGET_SPEC_VERSION
                                               , EXT_MEMORY_BUDGET_EXTENSION_NAME
                                               , pattern EXT_MEMORY_BUDGET_EXTENSION_NAME
                                               ) where

import Vulkan.CStruct.Utils (FixedArray)
import Control.Monad (unless)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.IO (throwIO)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
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 GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (Ptr)
import Data.Kind (Type)
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.APIConstants (MAX_MEMORY_HEAPS)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.APIConstants (pattern MAX_MEMORY_HEAPS)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_BUDGET_PROPERTIES_EXT))
-- | VkPhysicalDeviceMemoryBudgetPropertiesEXT - Structure specifying
-- physical device memory budget and usage
--
-- = Description
--
-- The values returned in this structure are not invariant. The
-- @heapBudget@ and @heapUsage@ values /must/ be zero for array elements
-- greater than or equal to
-- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceMemoryProperties'::@memoryHeapCount@.
-- The @heapBudget@ value /must/ be non-zero for array elements less than
-- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceMemoryProperties'::@memoryHeapCount@.
-- The @heapBudget@ value /must/ be less than or equal to
-- 'Vulkan.Core10.DeviceInitialization.MemoryHeap'::@size@ for each heap.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceMemoryBudgetPropertiesEXT = PhysicalDeviceMemoryBudgetPropertiesEXT
  { -- | @heapBudget@ is an array of
    -- 'Vulkan.Core10.APIConstants.MAX_MEMORY_HEAPS'
    -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' values in which memory
    -- budgets are returned, with one element for each memory heap. A heap’s
    -- budget is a rough estimate of how much memory the process /can/ allocate
    -- from that heap before allocations /may/ fail or cause performance
    -- degradation. The budget includes any currently allocated device memory.
    PhysicalDeviceMemoryBudgetPropertiesEXT -> Vector DeviceSize
heapBudget :: Vector DeviceSize
  , -- | @heapUsage@ is an array of 'Vulkan.Core10.APIConstants.MAX_MEMORY_HEAPS'
    -- 'Vulkan.Core10.FundamentalTypes.DeviceSize' values in which memory
    -- usages are returned, with one element for each memory heap. A heap’s
    -- usage is an estimate of how much memory the process is currently using
    -- in that heap.
    PhysicalDeviceMemoryBudgetPropertiesEXT -> Vector DeviceSize
heapUsage :: Vector DeviceSize
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceMemoryBudgetPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceMemoryBudgetPropertiesEXT

instance ToCStruct PhysicalDeviceMemoryBudgetPropertiesEXT where
  withCStruct :: PhysicalDeviceMemoryBudgetPropertiesEXT
-> (Ptr PhysicalDeviceMemoryBudgetPropertiesEXT -> IO b) -> IO b
withCStruct x :: PhysicalDeviceMemoryBudgetPropertiesEXT
x f :: Ptr PhysicalDeviceMemoryBudgetPropertiesEXT -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceMemoryBudgetPropertiesEXT -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 272 8 ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceMemoryBudgetPropertiesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p -> Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> PhysicalDeviceMemoryBudgetPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p PhysicalDeviceMemoryBudgetPropertiesEXT
x (Ptr PhysicalDeviceMemoryBudgetPropertiesEXT -> IO b
f Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p)
  pokeCStruct :: Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> PhysicalDeviceMemoryBudgetPropertiesEXT -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p PhysicalDeviceMemoryBudgetPropertiesEXT{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_BUDGET_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector DeviceSize -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DeviceSize -> Int) -> Vector DeviceSize -> Int
forall a b. (a -> b) -> a -> b
$ (Vector DeviceSize
heapBudget)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "heapBudget is too long, a maximum of MAX_MEMORY_HEAPS elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> DeviceSize -> IO ()) -> Vector DeviceSize -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DeviceSize
e -> Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize) -> Ptr DeviceSize
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> Int -> Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)))) Ptr DeviceSize -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) (DeviceSize
e)) (Vector DeviceSize
heapBudget)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector DeviceSize -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector DeviceSize -> Int) -> Vector DeviceSize -> Int
forall a b. (a -> b) -> a -> b
$ (Vector DeviceSize
heapUsage)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "heapUsage is too long, a maximum of MAX_MEMORY_HEAPS elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> DeviceSize -> IO ()) -> Vector DeviceSize -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DeviceSize
e -> Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize) -> Ptr DeviceSize
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> Int -> Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)))) Ptr DeviceSize -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) (DeviceSize
e)) (Vector DeviceSize
heapUsage)
    IO b
f
  cStructSize :: Int
cStructSize = 272
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceMemoryBudgetPropertiesEXT -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_MEMORY_BUDGET_PROPERTIES_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any -> Int) -> Vector Any -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "heapBudget is too long, a maximum of MAX_MEMORY_HEAPS elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> DeviceSize -> IO ()) -> Vector DeviceSize -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DeviceSize
e -> Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize) -> Ptr DeviceSize
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> Int -> Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)))) Ptr DeviceSize -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) (DeviceSize
e)) (Vector DeviceSize
forall a. Monoid a => a
mempty)
    Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any -> Int) -> Vector Any -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "heapUsage is too long, a maximum of MAX_MEMORY_HEAPS elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    (Int -> DeviceSize -> IO ()) -> Vector DeviceSize -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: DeviceSize
e -> Ptr DeviceSize -> DeviceSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize) -> Ptr DeviceSize
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> Int -> Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)))) Ptr DeviceSize -> Int -> Ptr DeviceSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) (DeviceSize
e)) (Vector DeviceSize
forall a. Monoid a => a
mempty)
    IO b
f

instance FromCStruct PhysicalDeviceMemoryBudgetPropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> IO PhysicalDeviceMemoryBudgetPropertiesEXT
peekCStruct p :: Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p = do
    Vector DeviceSize
heapBudget <- Int -> (Int -> IO DeviceSize) -> IO (Vector DeviceSize)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (\i :: Int
i -> Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (((Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize) -> Ptr DeviceSize
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @DeviceSize ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> Int -> Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)))) Ptr DeviceSize -> Int -> Ptr DeviceSize
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize)))
    Vector DeviceSize
heapUsage <- Int -> (Int -> IO DeviceSize) -> IO (Vector DeviceSize)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (\i :: Int
i -> Ptr DeviceSize -> IO DeviceSize
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (((Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize) -> Ptr DeviceSize
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @DeviceSize ((Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
p Ptr PhysicalDeviceMemoryBudgetPropertiesEXT
-> Int -> Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr (FixedArray MAX_MEMORY_HEAPS DeviceSize)))) Ptr DeviceSize -> Int -> Ptr DeviceSize
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize)))
    PhysicalDeviceMemoryBudgetPropertiesEXT
-> IO PhysicalDeviceMemoryBudgetPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceMemoryBudgetPropertiesEXT
 -> IO PhysicalDeviceMemoryBudgetPropertiesEXT)
-> PhysicalDeviceMemoryBudgetPropertiesEXT
-> IO PhysicalDeviceMemoryBudgetPropertiesEXT
forall a b. (a -> b) -> a -> b
$ Vector DeviceSize
-> Vector DeviceSize -> PhysicalDeviceMemoryBudgetPropertiesEXT
PhysicalDeviceMemoryBudgetPropertiesEXT
             Vector DeviceSize
heapBudget Vector DeviceSize
heapUsage

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

instance Zero PhysicalDeviceMemoryBudgetPropertiesEXT where
  zero :: PhysicalDeviceMemoryBudgetPropertiesEXT
zero = Vector DeviceSize
-> Vector DeviceSize -> PhysicalDeviceMemoryBudgetPropertiesEXT
PhysicalDeviceMemoryBudgetPropertiesEXT
           Vector DeviceSize
forall a. Monoid a => a
mempty
           Vector DeviceSize
forall a. Monoid a => a
mempty


type EXT_MEMORY_BUDGET_SPEC_VERSION = 1

-- No documentation found for TopLevel "VK_EXT_MEMORY_BUDGET_SPEC_VERSION"
pattern EXT_MEMORY_BUDGET_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_MEMORY_BUDGET_SPEC_VERSION :: a
$mEXT_MEMORY_BUDGET_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_MEMORY_BUDGET_SPEC_VERSION = 1


type EXT_MEMORY_BUDGET_EXTENSION_NAME = "VK_EXT_memory_budget"

-- No documentation found for TopLevel "VK_EXT_MEMORY_BUDGET_EXTENSION_NAME"
pattern EXT_MEMORY_BUDGET_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_MEMORY_BUDGET_EXTENSION_NAME :: a
$mEXT_MEMORY_BUDGET_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_MEMORY_BUDGET_EXTENSION_NAME = "VK_EXT_memory_budget"