{-# language CPP #-}
-- | = Name
--
-- VK_EXT_device_memory_report - device extension
--
-- == VK_EXT_device_memory_report
--
-- [__Name String__]
--     @VK_EXT_device_memory_report@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     285
--
-- [__Revision__]
--     2
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires Vulkan 1.0
--
--     -   Requires @VK_KHR_get_physical_device_properties2@
--
-- [__Special Use__]
--
--     -   <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#extendingvulkan-compatibility-specialuse Developer tools>
--
-- [__Contact__]
--
--     -   Yiwei Zhang
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_device_memory_report] @zhangyiwei%0A<<Here describe the issue or question you have about the VK_EXT_device_memory_report extension>> >
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2021-01-06
--
-- [__IP Status__]
--     No known IP claims.
--
-- [__Contributors__]
--
--     -   Yiwei Zhang, Google
--
--     -   Jesse Hall, Google
--
-- == Description
--
-- This device extension allows registration of device memory event
-- callbacks upon device creation, so that applications or middleware can
-- obtain detailed information about memory usage and how memory is
-- associated with Vulkan objects. This extension exposes the actual
-- underlying device memory usage, including allocations that are not
-- normally visible to the application, such as memory consumed by
-- 'Vulkan.Core10.Pipeline.createGraphicsPipelines'. It is intended
-- primarily for use by debug tooling rather than for production
-- applications.
--
-- == New Structures
--
-- -   'DeviceMemoryReportCallbackDataEXT'
--
-- -   Extending 'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'DeviceDeviceMemoryReportCreateInfoEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceDeviceMemoryReportFeaturesEXT'
--
-- == New Function Pointers
--
-- -   'PFN_vkDeviceMemoryReportCallbackEXT'
--
-- == New Enums
--
-- -   'DeviceMemoryReportEventTypeEXT'
--
-- == New Bitmasks
--
-- -   'DeviceMemoryReportFlagsEXT'
--
-- == New Enum Constants
--
-- -   'EXT_DEVICE_MEMORY_REPORT_EXTENSION_NAME'
--
-- -   'EXT_DEVICE_MEMORY_REPORT_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_DEVICE_MEMORY_REPORT_CREATE_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEVICE_MEMORY_REPORT_CALLBACK_DATA_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_MEMORY_REPORT_FEATURES_EXT'
--
-- == Issues
--
-- 1) Should this be better expressed as an extension to VK_EXT_debug_utils
-- and its general-purpose messenger construct?
--
-- __RESOLVED__: No. The intended lifecycle is quite different. We want to
-- make this extension tied to the device’s lifecycle. Each ICD just
-- handles its own implementation of this extension, and this extension
-- will only be directly exposed from the ICD. So we can avoid the extra
-- implementation complexity used to accommodate the flexibility of
-- @VK_EXT_debug_utils@ extension.
--
-- 2) Can we extend and use the existing internal allocation callbacks
-- instead of adding the new callback structure in this extension?
--
-- __RESOLVED__: No. Our memory reporting layer that combines this
-- information with other memory information it collects directly (e.g.
-- bindings of resources to 'Vulkan.Core10.Handles.DeviceMemory') would
-- have to intercept all entry points that take a
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' parameter and
-- inject its own @pfnInternalAllocation@ and @pfnInternalFree@. That may
-- be doable for the extensions we know about, but not for ones we do not.
-- The proposal would work fine in the face of most unknown extensions. But
-- even for ones we know about, since apps can provide a different set of
-- callbacks and userdata and those can be retained by the driver and used
-- later (esp. for pool object, but not just those), we would have to
-- dynamically allocate the interception trampoline every time. That is
-- getting to be an unreasonably large amount of complexity and (possibly)
-- overhead.
--
-- We are interested in both alloc\/free and import\/unimport. The latter
-- is fairly important for tracking (and avoiding double-counting) of
-- swapchain images (still true with “native swapchains” based on external
-- memory) and media\/camera interop. Though we might be able to handle
-- this with additional
-- 'Vulkan.Core10.Enums.InternalAllocationType.InternalAllocationType'
-- values, for import\/export we do want to be able to tie this to the
-- external resource, which is one thing that the @memoryObjectId@ is for.
--
-- The internal alloc\/free callbacks are not extensible except via new
-- 'Vulkan.Core10.Enums.InternalAllocationType.InternalAllocationType'
-- values. The 'DeviceMemoryReportCallbackDataEXT' in this extension is
-- extensible. That was deliberate: there is a real possibility we will
-- want to get extra information in the future. As one example, currently
-- this reports only physical allocations, but we believe there are
-- interesting cases for tracking how populated that VA region is.
--
-- The callbacks are clearly specified as only callable within the context
-- of a call from the app into Vulkan. We believe there are some cases
-- where drivers can allocate device memory asynchronously. This was one of
-- the sticky issues that derailed the internal device memory allocation
-- reporting design (which is essentially what this extension is trying to
-- do) leading up to 1.0.
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' is described in
-- a section called “Host memory” and the intro to it is very explicitly
-- about host memory. The other callbacks are all inherently about host
-- memory. But this extension is very focused on device memory.
--
-- 3) Should the callback be reporting which heap is used?
--
-- __RESOLVED__: Yes. It is important for non-UMA systems to have all the
-- device memory allocations attributed to the corresponding device memory
-- heaps. For internally-allocated device memory, @heapIndex@ will always
-- correspond to an advertised heap, rather than having a magic value
-- indicating a non-advertised heap. Drivers can advertise heaps that do
-- not have any corresponding memory types if they need to.
--
-- 4) Should we use an array of callback for the layers to intercept
-- instead of chaining multiple of the
-- 'DeviceDeviceMemoryReportCreateInfoEXT' structures in the @pNext@ of
-- 'Vulkan.Core10.Device.DeviceCreateInfo'?
--
-- __RESOLVED__ No. The pointer to the
-- 'DeviceDeviceMemoryReportCreateInfoEXT' structure itself is const and
-- you cannot just cast it away. Thus we cannot update the callback array
-- inside the structure. In addition, we cannot drop this @pNext@ chain
-- either, so making a copy of this whole structure does not work either.
--
-- 5) Should we track bulk allocations shared among multiple objects?
--
-- __RESOLVED__ No. Take the shader heap as an example. Some
-- implementations will let multiple 'Vulkan.Core10.Handles.Pipeline'
-- objects share the same shader heap. We are not asking the implementation
-- to report 'Vulkan.Core10.Enums.ObjectType.OBJECT_TYPE_PIPELINE' along
-- with a 'Vulkan.Core10.APIConstants.NULL_HANDLE' for this bulk
-- allocation. Instead, this bulk allocation is considered as a layer below
-- what this extension is interested in. Later, when the actual
-- 'Vulkan.Core10.Handles.Pipeline' objects are created by suballocating
-- from the bulk allocation, we ask the implementation to report the valid
-- handles of the 'Vulkan.Core10.Handles.Pipeline' objects along with the
-- actual suballocated sizes and different @memoryObjectId@.
--
-- 6) Can we require the callbacks to be always called in the same thread
-- with the Vulkan commands?
--
-- __RESOLVED__ No. Some implementations might choose to multiplex work
-- from multiple application threads into a single backend thread and
-- perform JIT allocations as a part of that flow. Since this behavior is
-- theoretically legit, we cannot require the callbacks to be always called
-- in the same thread with the Vulkan commands, and the note is to remind
-- the applications to handle this case properly.
--
-- 7) Should we add an additional “allocation failed” event type with
-- things like size and heap index reported?
--
-- __RESOLVED__ Yes. This fits in well with the callback infrastructure
-- added in this extension, and implementation touches the same code and
-- has the same overheads as the rest of the extension. It could help
-- debugging things like getting an
-- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' error when ending
-- a command buffer. Right now the allocation failure could have happened
-- anywhere during recording, and a callback would be really useful to
-- understand where and why.
--
-- == Version History
--
-- -   Revision 1, 2020-08-26 (Yiwei Zhang)
--
--     -   Initial version
--
-- -   Revision 2, 2021-01-06 (Yiwei Zhang)
--
--     -   Minor description update
--
-- = See Also
--
-- 'PFN_vkDeviceMemoryReportCallbackEXT',
-- 'DeviceDeviceMemoryReportCreateInfoEXT',
-- 'DeviceMemoryReportCallbackDataEXT', 'DeviceMemoryReportEventTypeEXT',
-- 'DeviceMemoryReportFlagsEXT',
-- 'PhysicalDeviceDeviceMemoryReportFeaturesEXT'
--
-- = Document Notes
--
-- For more information, see the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_device_memory_report Vulkan Specification>
--
-- This page is a generated document. Fixes and changes should be made to
-- the generator scripts, not directly.
module Vulkan.Extensions.VK_EXT_device_memory_report  ( PhysicalDeviceDeviceMemoryReportFeaturesEXT(..)
                                                      , DeviceDeviceMemoryReportCreateInfoEXT(..)
                                                      , DeviceMemoryReportCallbackDataEXT(..)
                                                      , DeviceMemoryReportFlagsEXT(..)
                                                      , DeviceMemoryReportEventTypeEXT( DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT
                                                                                      , DEVICE_MEMORY_REPORT_EVENT_TYPE_FREE_EXT
                                                                                      , DEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT
                                                                                      , DEVICE_MEMORY_REPORT_EVENT_TYPE_UNIMPORT_EXT
                                                                                      , DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT
                                                                                      , ..
                                                                                      )
                                                      , PFN_vkDeviceMemoryReportCallbackEXT
                                                      , FN_vkDeviceMemoryReportCallbackEXT
                                                      , EXT_DEVICE_MEMORY_REPORT_SPEC_VERSION
                                                      , pattern EXT_DEVICE_MEMORY_REPORT_SPEC_VERSION
                                                      , EXT_DEVICE_MEMORY_REPORT_EXTENSION_NAME
                                                      , pattern EXT_DEVICE_MEMORY_REPORT_EXTENSION_NAME
                                                      ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Numeric (showHex)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
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 Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Word (Word32)
import Data.Word (Word64)
import Data.Kind (Type)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Enums.ObjectType (ObjectType)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_DEVICE_MEMORY_REPORT_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEVICE_MEMORY_REPORT_CALLBACK_DATA_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_DEVICE_MEMORY_REPORT_FEATURES_EXT))
-- | VkPhysicalDeviceDeviceMemoryReportFeaturesEXT - Structure describing
-- whether device memory report callback can be supported by an
-- implementation
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceDeviceMemoryReportFeaturesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFeatures2',
-- it is filled in to indicate whether each corresponding feature is
-- supported. 'PhysicalDeviceDeviceMemoryReportFeaturesEXT' /can/ also be
-- used in the @pNext@ chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to
-- selectively enable these features.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_device_memory_report VK_EXT_device_memory_report>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceDeviceMemoryReportFeaturesEXT = PhysicalDeviceDeviceMemoryReportFeaturesEXT
  { -- | #features-deviceMemoryReport# @deviceMemoryReport@ indicates whether the
    -- implementation supports the ability to register device memory report
    -- callbacks.
    PhysicalDeviceDeviceMemoryReportFeaturesEXT -> Bool
deviceMemoryReport :: Bool }
  deriving (Typeable, PhysicalDeviceDeviceMemoryReportFeaturesEXT
-> PhysicalDeviceDeviceMemoryReportFeaturesEXT -> Bool
(PhysicalDeviceDeviceMemoryReportFeaturesEXT
 -> PhysicalDeviceDeviceMemoryReportFeaturesEXT -> Bool)
-> (PhysicalDeviceDeviceMemoryReportFeaturesEXT
    -> PhysicalDeviceDeviceMemoryReportFeaturesEXT -> Bool)
-> Eq PhysicalDeviceDeviceMemoryReportFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceDeviceMemoryReportFeaturesEXT
-> PhysicalDeviceDeviceMemoryReportFeaturesEXT -> Bool
$c/= :: PhysicalDeviceDeviceMemoryReportFeaturesEXT
-> PhysicalDeviceDeviceMemoryReportFeaturesEXT -> Bool
== :: PhysicalDeviceDeviceMemoryReportFeaturesEXT
-> PhysicalDeviceDeviceMemoryReportFeaturesEXT -> Bool
$c== :: PhysicalDeviceDeviceMemoryReportFeaturesEXT
-> PhysicalDeviceDeviceMemoryReportFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceDeviceMemoryReportFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceDeviceMemoryReportFeaturesEXT

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

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

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

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


-- | VkDeviceDeviceMemoryReportCreateInfoEXT - Register device memory report
-- callbacks for a Vulkan device
--
-- = Description
--
-- The callback /may/ be called from multiple threads simultaneously.
--
-- The callback /must/ be called only once by the implementation when a
-- 'DeviceMemoryReportEventTypeEXT' event occurs.
--
-- Note
--
-- The callback could be called from a background thread other than the
-- thread calling the Vulkan commands.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'PFN_vkDeviceMemoryReportCallbackEXT',
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_device_memory_report VK_EXT_device_memory_report>,
-- 'DeviceMemoryReportFlagsEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceDeviceMemoryReportCreateInfoEXT = DeviceDeviceMemoryReportCreateInfoEXT
  { -- | @flags@ is 0 and reserved for future use.
    --
    -- #VUID-VkDeviceDeviceMemoryReportCreateInfoEXT-flags-zerobitmask# @flags@
    -- /must/ be @0@
    DeviceDeviceMemoryReportCreateInfoEXT -> DeviceMemoryReportFlagsEXT
flags :: DeviceMemoryReportFlagsEXT
  , -- | @pfnUserCallback@ is the application callback function to call.
    --
    -- #VUID-VkDeviceDeviceMemoryReportCreateInfoEXT-pfnUserCallback-parameter#
    -- @pfnUserCallback@ /must/ be a valid
    -- 'PFN_vkDeviceMemoryReportCallbackEXT' value
    DeviceDeviceMemoryReportCreateInfoEXT
-> PFN_vkDeviceMemoryReportCallbackEXT
pfnUserCallback :: PFN_vkDeviceMemoryReportCallbackEXT
  , -- | @pUserData@ is user data to be passed to the callback.
    --
    -- #VUID-VkDeviceDeviceMemoryReportCreateInfoEXT-pUserData-parameter#
    -- @pUserData@ /must/ be a pointer value
    DeviceDeviceMemoryReportCreateInfoEXT -> Ptr ()
userData :: Ptr ()
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceDeviceMemoryReportCreateInfoEXT)
#endif
deriving instance Show DeviceDeviceMemoryReportCreateInfoEXT

instance ToCStruct DeviceDeviceMemoryReportCreateInfoEXT where
  withCStruct :: DeviceDeviceMemoryReportCreateInfoEXT
-> (Ptr DeviceDeviceMemoryReportCreateInfoEXT -> IO b) -> IO b
withCStruct DeviceDeviceMemoryReportCreateInfoEXT
x Ptr DeviceDeviceMemoryReportCreateInfoEXT -> IO b
f = Int -> (Ptr DeviceDeviceMemoryReportCreateInfoEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((Ptr DeviceDeviceMemoryReportCreateInfoEXT -> IO b) -> IO b)
-> (Ptr DeviceDeviceMemoryReportCreateInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr DeviceDeviceMemoryReportCreateInfoEXT
p -> Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> DeviceDeviceMemoryReportCreateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceDeviceMemoryReportCreateInfoEXT
p DeviceDeviceMemoryReportCreateInfoEXT
x (Ptr DeviceDeviceMemoryReportCreateInfoEXT -> IO b
f Ptr DeviceDeviceMemoryReportCreateInfoEXT
p)
  pokeCStruct :: Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> DeviceDeviceMemoryReportCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr DeviceDeviceMemoryReportCreateInfoEXT
p DeviceDeviceMemoryReportCreateInfoEXT{Ptr ()
PFN_vkDeviceMemoryReportCallbackEXT
DeviceMemoryReportFlagsEXT
userData :: Ptr ()
pfnUserCallback :: PFN_vkDeviceMemoryReportCallbackEXT
flags :: DeviceMemoryReportFlagsEXT
$sel:userData:DeviceDeviceMemoryReportCreateInfoEXT :: DeviceDeviceMemoryReportCreateInfoEXT -> Ptr ()
$sel:pfnUserCallback:DeviceDeviceMemoryReportCreateInfoEXT :: DeviceDeviceMemoryReportCreateInfoEXT
-> PFN_vkDeviceMemoryReportCallbackEXT
$sel:flags:DeviceDeviceMemoryReportCreateInfoEXT :: DeviceDeviceMemoryReportCreateInfoEXT -> DeviceMemoryReportFlagsEXT
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_DEVICE_MEMORY_REPORT_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> Int -> Ptr DeviceMemoryReportFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemoryReportFlagsEXT)) (DeviceMemoryReportFlagsEXT
flags)
    Ptr PFN_vkDeviceMemoryReportCallbackEXT
-> PFN_vkDeviceMemoryReportCallbackEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> Int -> Ptr PFN_vkDeviceMemoryReportCallbackEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr PFN_vkDeviceMemoryReportCallbackEXT)) (PFN_vkDeviceMemoryReportCallbackEXT
pfnUserCallback)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ()))) (Ptr ()
userData)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr DeviceDeviceMemoryReportCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr DeviceDeviceMemoryReportCreateInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_DEVICE_MEMORY_REPORT_CREATE_INFO_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> Int -> Ptr DeviceMemoryReportFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemoryReportFlagsEXT)) (DeviceMemoryReportFlagsEXT
forall a. Zero a => a
zero)
    Ptr PFN_vkDeviceMemoryReportCallbackEXT
-> PFN_vkDeviceMemoryReportCallbackEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> Int -> Ptr PFN_vkDeviceMemoryReportCallbackEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr PFN_vkDeviceMemoryReportCallbackEXT)) (PFN_vkDeviceMemoryReportCallbackEXT
forall a. Zero a => a
zero)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ()))) (Ptr ()
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DeviceDeviceMemoryReportCreateInfoEXT where
  peekCStruct :: Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> IO DeviceDeviceMemoryReportCreateInfoEXT
peekCStruct Ptr DeviceDeviceMemoryReportCreateInfoEXT
p = do
    DeviceMemoryReportFlagsEXT
flags <- Ptr DeviceMemoryReportFlagsEXT -> IO DeviceMemoryReportFlagsEXT
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemoryReportFlagsEXT ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> Int -> Ptr DeviceMemoryReportFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemoryReportFlagsEXT))
    PFN_vkDeviceMemoryReportCallbackEXT
pfnUserCallback <- Ptr PFN_vkDeviceMemoryReportCallbackEXT
-> IO PFN_vkDeviceMemoryReportCallbackEXT
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkDeviceMemoryReportCallbackEXT ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT
-> Int -> Ptr PFN_vkDeviceMemoryReportCallbackEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr PFN_vkDeviceMemoryReportCallbackEXT))
    Ptr ()
pUserData <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr DeviceDeviceMemoryReportCreateInfoEXT
p Ptr DeviceDeviceMemoryReportCreateInfoEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ())))
    DeviceDeviceMemoryReportCreateInfoEXT
-> IO DeviceDeviceMemoryReportCreateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceDeviceMemoryReportCreateInfoEXT
 -> IO DeviceDeviceMemoryReportCreateInfoEXT)
-> DeviceDeviceMemoryReportCreateInfoEXT
-> IO DeviceDeviceMemoryReportCreateInfoEXT
forall a b. (a -> b) -> a -> b
$ DeviceMemoryReportFlagsEXT
-> PFN_vkDeviceMemoryReportCallbackEXT
-> Ptr ()
-> DeviceDeviceMemoryReportCreateInfoEXT
DeviceDeviceMemoryReportCreateInfoEXT
             DeviceMemoryReportFlagsEXT
flags PFN_vkDeviceMemoryReportCallbackEXT
pfnUserCallback Ptr ()
pUserData

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

instance Zero DeviceDeviceMemoryReportCreateInfoEXT where
  zero :: DeviceDeviceMemoryReportCreateInfoEXT
zero = DeviceMemoryReportFlagsEXT
-> PFN_vkDeviceMemoryReportCallbackEXT
-> Ptr ()
-> DeviceDeviceMemoryReportCreateInfoEXT
DeviceDeviceMemoryReportCreateInfoEXT
           DeviceMemoryReportFlagsEXT
forall a. Zero a => a
zero
           PFN_vkDeviceMemoryReportCallbackEXT
forall a. Zero a => a
zero
           Ptr ()
forall a. Zero a => a
zero


-- | VkDeviceMemoryReportCallbackDataEXT - Structure specifying parameters
-- returned to the callback
--
-- = Description
--
-- @memoryObjectId@ is used to avoid double-counting on the same memory
-- object.
--
-- If an internally-allocated device memory object or a
-- 'Vulkan.Core10.Handles.DeviceMemory' /cannot/ be exported,
-- @memoryObjectId@ /must/ be unique in the 'Vulkan.Core10.Handles.Device'.
--
-- If an internally-allocated device memory object or a
-- 'Vulkan.Core10.Handles.DeviceMemory' supports being exported,
-- @memoryObjectId@ /must/ be unique system wide.
--
-- If an internal device memory object or a
-- 'Vulkan.Core10.Handles.DeviceMemory' is backed by an imported external
-- memory object, @memoryObjectId@ /must/ be unique system wide.
--
-- Note
--
-- This structure should only be considered valid during the lifetime of
-- the triggered callback.
--
-- For 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT' and
-- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT' events, @objectHandle@
-- usually will not yet exist when the application or tool receives the
-- callback. @objectHandle@ will only exist when the create or allocate
-- call that triggered the event returns, and if the allocation or import
-- ends up failing @objectHandle@ will not ever exist.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_device_memory_report VK_EXT_device_memory_report>,
-- 'DeviceMemoryReportEventTypeEXT', 'DeviceMemoryReportFlagsEXT',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.ObjectType.ObjectType',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeviceMemoryReportCallbackDataEXT = DeviceMemoryReportCallbackDataEXT
  { -- | @flags@ is 0 and reserved for future use.
    DeviceMemoryReportCallbackDataEXT -> DeviceMemoryReportFlagsEXT
flags :: DeviceMemoryReportFlagsEXT
  , -- | @type@ is a 'DeviceMemoryReportEventTypeEXT' type specifying the type of
    -- event reported in this 'DeviceMemoryReportCallbackDataEXT' structure.
    DeviceMemoryReportCallbackDataEXT -> DeviceMemoryReportEventTypeEXT
type' :: DeviceMemoryReportEventTypeEXT
  , -- | @memoryObjectId@ is the unique id for the underlying memory object as
    -- described below.
    DeviceMemoryReportCallbackDataEXT -> Word64
memoryObjectId :: Word64
  , -- | @size@ is the size of the memory object in bytes. If @type@ is
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT',
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT' or
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT', @size@ is a
    -- valid 'Vulkan.Core10.FundamentalTypes.DeviceSize' value. Otherwise,
    -- @size@ is undefined.
    DeviceMemoryReportCallbackDataEXT -> Word64
size :: DeviceSize
  , -- | @objectType@ is a 'Vulkan.Core10.Enums.ObjectType.ObjectType' value
    -- specifying the type of the object associated with this device memory
    -- report event. If @type@ is
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT',
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_FREE_EXT',
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT',
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_UNIMPORT_EXT' or
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT', @objectType@ is
    -- a valid 'Vulkan.Core10.Enums.ObjectType.ObjectType' enum. Otherwise,
    -- @objectType@ is undefined.
    DeviceMemoryReportCallbackDataEXT -> ObjectType
objectType :: ObjectType
  , -- | @objectHandle@ is the object this device memory report event is
    -- attributed to. If @type@ is
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT',
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_FREE_EXT',
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT' or
    -- 'DEVICE_MEMORY_REPORT_EVENT_TYPE_UNIMPORT_EXT', @objectHandle@ is a
    -- valid Vulkan handle of the type associated with @objectType@ as defined
    -- in the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#debugging-object-types VkObjectType and Vulkan Handle Relationship>
    -- table. Otherwise, @objectHandle@ is undefined.
    DeviceMemoryReportCallbackDataEXT -> Word64
objectHandle :: Word64
  , -- | @heapIndex@ describes which memory heap this device memory allocation is
    -- made from. If @type@ is 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT'
    -- or 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT', @heapIndex@
    -- corresponds to one of the valid heaps from the
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceMemoryProperties'
    -- structure. Otherwise, @heapIndex@ is undefined.
    DeviceMemoryReportCallbackDataEXT -> Word32
heapIndex :: Word32
  }
  deriving (Typeable, DeviceMemoryReportCallbackDataEXT
-> DeviceMemoryReportCallbackDataEXT -> Bool
(DeviceMemoryReportCallbackDataEXT
 -> DeviceMemoryReportCallbackDataEXT -> Bool)
-> (DeviceMemoryReportCallbackDataEXT
    -> DeviceMemoryReportCallbackDataEXT -> Bool)
-> Eq DeviceMemoryReportCallbackDataEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceMemoryReportCallbackDataEXT
-> DeviceMemoryReportCallbackDataEXT -> Bool
$c/= :: DeviceMemoryReportCallbackDataEXT
-> DeviceMemoryReportCallbackDataEXT -> Bool
== :: DeviceMemoryReportCallbackDataEXT
-> DeviceMemoryReportCallbackDataEXT -> Bool
$c== :: DeviceMemoryReportCallbackDataEXT
-> DeviceMemoryReportCallbackDataEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceMemoryReportCallbackDataEXT)
#endif
deriving instance Show DeviceMemoryReportCallbackDataEXT

instance ToCStruct DeviceMemoryReportCallbackDataEXT where
  withCStruct :: DeviceMemoryReportCallbackDataEXT
-> (Ptr DeviceMemoryReportCallbackDataEXT -> IO b) -> IO b
withCStruct DeviceMemoryReportCallbackDataEXT
x Ptr DeviceMemoryReportCallbackDataEXT -> IO b
f = Int -> (Ptr DeviceMemoryReportCallbackDataEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
64 ((Ptr DeviceMemoryReportCallbackDataEXT -> IO b) -> IO b)
-> (Ptr DeviceMemoryReportCallbackDataEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr DeviceMemoryReportCallbackDataEXT
p -> Ptr DeviceMemoryReportCallbackDataEXT
-> DeviceMemoryReportCallbackDataEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceMemoryReportCallbackDataEXT
p DeviceMemoryReportCallbackDataEXT
x (Ptr DeviceMemoryReportCallbackDataEXT -> IO b
f Ptr DeviceMemoryReportCallbackDataEXT
p)
  pokeCStruct :: Ptr DeviceMemoryReportCallbackDataEXT
-> DeviceMemoryReportCallbackDataEXT -> IO b -> IO b
pokeCStruct Ptr DeviceMemoryReportCallbackDataEXT
p DeviceMemoryReportCallbackDataEXT{Word32
Word64
ObjectType
DeviceMemoryReportEventTypeEXT
DeviceMemoryReportFlagsEXT
heapIndex :: Word32
objectHandle :: Word64
objectType :: ObjectType
size :: Word64
memoryObjectId :: Word64
type' :: DeviceMemoryReportEventTypeEXT
flags :: DeviceMemoryReportFlagsEXT
$sel:heapIndex:DeviceMemoryReportCallbackDataEXT :: DeviceMemoryReportCallbackDataEXT -> Word32
$sel:objectHandle:DeviceMemoryReportCallbackDataEXT :: DeviceMemoryReportCallbackDataEXT -> Word64
$sel:objectType:DeviceMemoryReportCallbackDataEXT :: DeviceMemoryReportCallbackDataEXT -> ObjectType
$sel:size:DeviceMemoryReportCallbackDataEXT :: DeviceMemoryReportCallbackDataEXT -> Word64
$sel:memoryObjectId:DeviceMemoryReportCallbackDataEXT :: DeviceMemoryReportCallbackDataEXT -> Word64
$sel:type':DeviceMemoryReportCallbackDataEXT :: DeviceMemoryReportCallbackDataEXT -> DeviceMemoryReportEventTypeEXT
$sel:flags:DeviceMemoryReportCallbackDataEXT :: DeviceMemoryReportCallbackDataEXT -> DeviceMemoryReportFlagsEXT
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_MEMORY_REPORT_CALLBACK_DATA_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT
-> Int -> Ptr DeviceMemoryReportFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemoryReportFlagsEXT)) (DeviceMemoryReportFlagsEXT
flags)
    Ptr DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT
-> Int -> Ptr DeviceMemoryReportEventTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr DeviceMemoryReportEventTypeEXT)) (DeviceMemoryReportEventTypeEXT
type')
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
memoryObjectId)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) (Word64
size)
    Ptr ObjectType -> ObjectType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr ObjectType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ObjectType)) (ObjectType
objectType)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word64)) (Word64
objectHandle)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32)) (Word32
heapIndex)
    IO b
f
  cStructSize :: Int
cStructSize = Int
64
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr DeviceMemoryReportCallbackDataEXT -> IO b -> IO b
pokeZeroCStruct Ptr DeviceMemoryReportCallbackDataEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEVICE_MEMORY_REPORT_CALLBACK_DATA_EXT)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    Ptr DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT
-> Int -> Ptr DeviceMemoryReportFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemoryReportFlagsEXT)) (DeviceMemoryReportFlagsEXT
forall a. Zero a => a
zero)
    Ptr DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT
-> Int -> Ptr DeviceMemoryReportEventTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr DeviceMemoryReportEventTypeEXT)) (DeviceMemoryReportEventTypeEXT
forall a. Zero a => a
zero)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) (Word64
forall a. Zero a => a
zero)
    Ptr ObjectType -> ObjectType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr ObjectType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ObjectType)) (ObjectType
forall a. Zero a => a
zero)
    Ptr Word64 -> Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word64)) (Word64
forall a. Zero a => a
zero)
    Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32)) (Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct DeviceMemoryReportCallbackDataEXT where
  peekCStruct :: Ptr DeviceMemoryReportCallbackDataEXT
-> IO DeviceMemoryReportCallbackDataEXT
peekCStruct Ptr DeviceMemoryReportCallbackDataEXT
p = do
    DeviceMemoryReportFlagsEXT
flags <- Ptr DeviceMemoryReportFlagsEXT -> IO DeviceMemoryReportFlagsEXT
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemoryReportFlagsEXT ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT
-> Int -> Ptr DeviceMemoryReportFlagsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceMemoryReportFlagsEXT))
    DeviceMemoryReportEventTypeEXT
type' <- Ptr DeviceMemoryReportEventTypeEXT
-> IO DeviceMemoryReportEventTypeEXT
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemoryReportEventTypeEXT ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT
-> Int -> Ptr DeviceMemoryReportEventTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr DeviceMemoryReportEventTypeEXT))
    Word64
memoryObjectId <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Word64))
    Word64
size <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize))
    ObjectType
objectType <- Ptr ObjectType -> IO ObjectType
forall a. Storable a => Ptr a -> IO a
peek @ObjectType ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr ObjectType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr ObjectType))
    Word64
objectHandle <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word64
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr Word64))
    Word32
heapIndex <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DeviceMemoryReportCallbackDataEXT
p Ptr DeviceMemoryReportCallbackDataEXT -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr Word32))
    DeviceMemoryReportCallbackDataEXT
-> IO DeviceMemoryReportCallbackDataEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceMemoryReportCallbackDataEXT
 -> IO DeviceMemoryReportCallbackDataEXT)
-> DeviceMemoryReportCallbackDataEXT
-> IO DeviceMemoryReportCallbackDataEXT
forall a b. (a -> b) -> a -> b
$ DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportEventTypeEXT
-> Word64
-> Word64
-> ObjectType
-> Word64
-> Word32
-> DeviceMemoryReportCallbackDataEXT
DeviceMemoryReportCallbackDataEXT
             DeviceMemoryReportFlagsEXT
flags DeviceMemoryReportEventTypeEXT
type' Word64
memoryObjectId Word64
size ObjectType
objectType Word64
objectHandle Word32
heapIndex

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

instance Zero DeviceMemoryReportCallbackDataEXT where
  zero :: DeviceMemoryReportCallbackDataEXT
zero = DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportEventTypeEXT
-> Word64
-> Word64
-> ObjectType
-> Word64
-> Word32
-> DeviceMemoryReportCallbackDataEXT
DeviceMemoryReportCallbackDataEXT
           DeviceMemoryReportFlagsEXT
forall a. Zero a => a
zero
           DeviceMemoryReportEventTypeEXT
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero
           ObjectType
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero
           Word32
forall a. Zero a => a
zero


-- | VkDeviceMemoryReportFlagsEXT - Reserved for future use
--
-- = Description
--
-- 'DeviceMemoryReportFlagsEXT' is a bitmask type for setting a mask, but
-- is currently reserved for future use.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_device_memory_report VK_EXT_device_memory_report>,
-- 'DeviceDeviceMemoryReportCreateInfoEXT',
-- 'DeviceMemoryReportCallbackDataEXT'
newtype DeviceMemoryReportFlagsEXT = DeviceMemoryReportFlagsEXT Flags
  deriving newtype (DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
(DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool)
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> Bool)
-> Eq DeviceMemoryReportFlagsEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
$c/= :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
== :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
$c== :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
Eq, Eq DeviceMemoryReportFlagsEXT
Eq DeviceMemoryReportFlagsEXT
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> Ordering)
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> Bool)
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> Bool)
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> Bool)
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> Bool)
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT)
-> Ord DeviceMemoryReportFlagsEXT
DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> Ordering
DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
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 :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
$cmin :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
max :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
$cmax :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
>= :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
$c>= :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
> :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
$c> :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
<= :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
$c<= :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
< :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
$c< :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT -> Bool
compare :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> Ordering
$ccompare :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> Ordering
$cp1Ord :: Eq DeviceMemoryReportFlagsEXT
Ord, Ptr b -> Int -> IO DeviceMemoryReportFlagsEXT
Ptr b -> Int -> DeviceMemoryReportFlagsEXT -> IO ()
Ptr DeviceMemoryReportFlagsEXT -> IO DeviceMemoryReportFlagsEXT
Ptr DeviceMemoryReportFlagsEXT
-> Int -> IO DeviceMemoryReportFlagsEXT
Ptr DeviceMemoryReportFlagsEXT
-> Int -> DeviceMemoryReportFlagsEXT -> IO ()
Ptr DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> IO ()
DeviceMemoryReportFlagsEXT -> Int
(DeviceMemoryReportFlagsEXT -> Int)
-> (DeviceMemoryReportFlagsEXT -> Int)
-> (Ptr DeviceMemoryReportFlagsEXT
    -> Int -> IO DeviceMemoryReportFlagsEXT)
-> (Ptr DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DeviceMemoryReportFlagsEXT)
-> (forall b. Ptr b -> Int -> DeviceMemoryReportFlagsEXT -> IO ())
-> (Ptr DeviceMemoryReportFlagsEXT
    -> IO DeviceMemoryReportFlagsEXT)
-> (Ptr DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> IO ())
-> Storable DeviceMemoryReportFlagsEXT
forall b. Ptr b -> Int -> IO DeviceMemoryReportFlagsEXT
forall b. Ptr b -> Int -> DeviceMemoryReportFlagsEXT -> 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 DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> IO ()
$cpoke :: Ptr DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> IO ()
peek :: Ptr DeviceMemoryReportFlagsEXT -> IO DeviceMemoryReportFlagsEXT
$cpeek :: Ptr DeviceMemoryReportFlagsEXT -> IO DeviceMemoryReportFlagsEXT
pokeByteOff :: Ptr b -> Int -> DeviceMemoryReportFlagsEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DeviceMemoryReportFlagsEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO DeviceMemoryReportFlagsEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DeviceMemoryReportFlagsEXT
pokeElemOff :: Ptr DeviceMemoryReportFlagsEXT
-> Int -> DeviceMemoryReportFlagsEXT -> IO ()
$cpokeElemOff :: Ptr DeviceMemoryReportFlagsEXT
-> Int -> DeviceMemoryReportFlagsEXT -> IO ()
peekElemOff :: Ptr DeviceMemoryReportFlagsEXT
-> Int -> IO DeviceMemoryReportFlagsEXT
$cpeekElemOff :: Ptr DeviceMemoryReportFlagsEXT
-> Int -> IO DeviceMemoryReportFlagsEXT
alignment :: DeviceMemoryReportFlagsEXT -> Int
$calignment :: DeviceMemoryReportFlagsEXT -> Int
sizeOf :: DeviceMemoryReportFlagsEXT -> Int
$csizeOf :: DeviceMemoryReportFlagsEXT -> Int
Storable, DeviceMemoryReportFlagsEXT
DeviceMemoryReportFlagsEXT -> Zero DeviceMemoryReportFlagsEXT
forall a. a -> Zero a
zero :: DeviceMemoryReportFlagsEXT
$czero :: DeviceMemoryReportFlagsEXT
Zero, Eq DeviceMemoryReportFlagsEXT
DeviceMemoryReportFlagsEXT
Eq DeviceMemoryReportFlagsEXT
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> DeviceMemoryReportFlagsEXT
-> (Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT -> Int -> Bool)
-> (DeviceMemoryReportFlagsEXT -> Maybe Int)
-> (DeviceMemoryReportFlagsEXT -> Int)
-> (DeviceMemoryReportFlagsEXT -> Bool)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT
    -> Int -> DeviceMemoryReportFlagsEXT)
-> (DeviceMemoryReportFlagsEXT -> Int)
-> Bits DeviceMemoryReportFlagsEXT
Int -> DeviceMemoryReportFlagsEXT
DeviceMemoryReportFlagsEXT -> Bool
DeviceMemoryReportFlagsEXT -> Int
DeviceMemoryReportFlagsEXT -> Maybe Int
DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
DeviceMemoryReportFlagsEXT -> Int -> Bool
DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
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 :: DeviceMemoryReportFlagsEXT -> Int
$cpopCount :: DeviceMemoryReportFlagsEXT -> Int
rotateR :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$crotateR :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
rotateL :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$crotateL :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
unsafeShiftR :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$cunsafeShiftR :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
shiftR :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$cshiftR :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
unsafeShiftL :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$cunsafeShiftL :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
shiftL :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$cshiftL :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
isSigned :: DeviceMemoryReportFlagsEXT -> Bool
$cisSigned :: DeviceMemoryReportFlagsEXT -> Bool
bitSize :: DeviceMemoryReportFlagsEXT -> Int
$cbitSize :: DeviceMemoryReportFlagsEXT -> Int
bitSizeMaybe :: DeviceMemoryReportFlagsEXT -> Maybe Int
$cbitSizeMaybe :: DeviceMemoryReportFlagsEXT -> Maybe Int
testBit :: DeviceMemoryReportFlagsEXT -> Int -> Bool
$ctestBit :: DeviceMemoryReportFlagsEXT -> Int -> Bool
complementBit :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$ccomplementBit :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
clearBit :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$cclearBit :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
setBit :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$csetBit :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
bit :: Int -> DeviceMemoryReportFlagsEXT
$cbit :: Int -> DeviceMemoryReportFlagsEXT
zeroBits :: DeviceMemoryReportFlagsEXT
$czeroBits :: DeviceMemoryReportFlagsEXT
rotate :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$crotate :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
shift :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
$cshift :: DeviceMemoryReportFlagsEXT -> Int -> DeviceMemoryReportFlagsEXT
complement :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
$ccomplement :: DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
xor :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
$cxor :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
.|. :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
$c.|. :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
.&. :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
$c.&. :: DeviceMemoryReportFlagsEXT
-> DeviceMemoryReportFlagsEXT -> DeviceMemoryReportFlagsEXT
$cp1Bits :: Eq DeviceMemoryReportFlagsEXT
Bits, Bits DeviceMemoryReportFlagsEXT
Bits DeviceMemoryReportFlagsEXT
-> (DeviceMemoryReportFlagsEXT -> Int)
-> (DeviceMemoryReportFlagsEXT -> Int)
-> (DeviceMemoryReportFlagsEXT -> Int)
-> FiniteBits DeviceMemoryReportFlagsEXT
DeviceMemoryReportFlagsEXT -> Int
forall b.
Bits b -> (b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
countTrailingZeros :: DeviceMemoryReportFlagsEXT -> Int
$ccountTrailingZeros :: DeviceMemoryReportFlagsEXT -> Int
countLeadingZeros :: DeviceMemoryReportFlagsEXT -> Int
$ccountLeadingZeros :: DeviceMemoryReportFlagsEXT -> Int
finiteBitSize :: DeviceMemoryReportFlagsEXT -> Int
$cfiniteBitSize :: DeviceMemoryReportFlagsEXT -> Int
$cp1FiniteBits :: Bits DeviceMemoryReportFlagsEXT
FiniteBits)



conNameDeviceMemoryReportFlagsEXT :: String
conNameDeviceMemoryReportFlagsEXT :: String
conNameDeviceMemoryReportFlagsEXT = String
"DeviceMemoryReportFlagsEXT"

enumPrefixDeviceMemoryReportFlagsEXT :: String
enumPrefixDeviceMemoryReportFlagsEXT :: String
enumPrefixDeviceMemoryReportFlagsEXT = String
""

showTableDeviceMemoryReportFlagsEXT :: [(DeviceMemoryReportFlagsEXT, String)]
showTableDeviceMemoryReportFlagsEXT :: [(DeviceMemoryReportFlagsEXT, String)]
showTableDeviceMemoryReportFlagsEXT = []

instance Show DeviceMemoryReportFlagsEXT where
  showsPrec :: Int -> DeviceMemoryReportFlagsEXT -> ShowS
showsPrec = String
-> [(DeviceMemoryReportFlagsEXT, String)]
-> String
-> (DeviceMemoryReportFlagsEXT -> Word32)
-> (Word32 -> ShowS)
-> Int
-> DeviceMemoryReportFlagsEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixDeviceMemoryReportFlagsEXT
                            [(DeviceMemoryReportFlagsEXT, String)]
showTableDeviceMemoryReportFlagsEXT
                            String
conNameDeviceMemoryReportFlagsEXT
                            (\(DeviceMemoryReportFlagsEXT Word32
x) -> Word32
x)
                            (\Word32
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Word32
x)

instance Read DeviceMemoryReportFlagsEXT where
  readPrec :: ReadPrec DeviceMemoryReportFlagsEXT
readPrec = String
-> [(DeviceMemoryReportFlagsEXT, String)]
-> String
-> (Word32 -> DeviceMemoryReportFlagsEXT)
-> ReadPrec DeviceMemoryReportFlagsEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixDeviceMemoryReportFlagsEXT
                          [(DeviceMemoryReportFlagsEXT, String)]
showTableDeviceMemoryReportFlagsEXT
                          String
conNameDeviceMemoryReportFlagsEXT
                          Word32 -> DeviceMemoryReportFlagsEXT
DeviceMemoryReportFlagsEXT


-- | VkDeviceMemoryReportEventTypeEXT - Events that can occur on a device
-- memory object
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_device_memory_report VK_EXT_device_memory_report>,
-- 'DeviceMemoryReportCallbackDataEXT'
newtype DeviceMemoryReportEventTypeEXT = DeviceMemoryReportEventTypeEXT Int32
  deriving newtype (DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
(DeviceMemoryReportEventTypeEXT
 -> DeviceMemoryReportEventTypeEXT -> Bool)
-> (DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT -> Bool)
-> Eq DeviceMemoryReportEventTypeEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
$c/= :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
== :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
$c== :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
Eq, Eq DeviceMemoryReportEventTypeEXT
Eq DeviceMemoryReportEventTypeEXT
-> (DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT -> Ordering)
-> (DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT -> Bool)
-> (DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT -> Bool)
-> (DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT -> Bool)
-> (DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT -> Bool)
-> (DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT)
-> (DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT)
-> Ord DeviceMemoryReportEventTypeEXT
DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Ordering
DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> DeviceMemoryReportEventTypeEXT
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 :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> DeviceMemoryReportEventTypeEXT
$cmin :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> DeviceMemoryReportEventTypeEXT
max :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> DeviceMemoryReportEventTypeEXT
$cmax :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> DeviceMemoryReportEventTypeEXT
>= :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
$c>= :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
> :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
$c> :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
<= :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
$c<= :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
< :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
$c< :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Bool
compare :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Ordering
$ccompare :: DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> Ordering
$cp1Ord :: Eq DeviceMemoryReportEventTypeEXT
Ord, Ptr b -> Int -> IO DeviceMemoryReportEventTypeEXT
Ptr b -> Int -> DeviceMemoryReportEventTypeEXT -> IO ()
Ptr DeviceMemoryReportEventTypeEXT
-> IO DeviceMemoryReportEventTypeEXT
Ptr DeviceMemoryReportEventTypeEXT
-> Int -> IO DeviceMemoryReportEventTypeEXT
Ptr DeviceMemoryReportEventTypeEXT
-> Int -> DeviceMemoryReportEventTypeEXT -> IO ()
Ptr DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> IO ()
DeviceMemoryReportEventTypeEXT -> Int
(DeviceMemoryReportEventTypeEXT -> Int)
-> (DeviceMemoryReportEventTypeEXT -> Int)
-> (Ptr DeviceMemoryReportEventTypeEXT
    -> Int -> IO DeviceMemoryReportEventTypeEXT)
-> (Ptr DeviceMemoryReportEventTypeEXT
    -> Int -> DeviceMemoryReportEventTypeEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO DeviceMemoryReportEventTypeEXT)
-> (forall b.
    Ptr b -> Int -> DeviceMemoryReportEventTypeEXT -> IO ())
-> (Ptr DeviceMemoryReportEventTypeEXT
    -> IO DeviceMemoryReportEventTypeEXT)
-> (Ptr DeviceMemoryReportEventTypeEXT
    -> DeviceMemoryReportEventTypeEXT -> IO ())
-> Storable DeviceMemoryReportEventTypeEXT
forall b. Ptr b -> Int -> IO DeviceMemoryReportEventTypeEXT
forall b. Ptr b -> Int -> DeviceMemoryReportEventTypeEXT -> 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 DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> IO ()
$cpoke :: Ptr DeviceMemoryReportEventTypeEXT
-> DeviceMemoryReportEventTypeEXT -> IO ()
peek :: Ptr DeviceMemoryReportEventTypeEXT
-> IO DeviceMemoryReportEventTypeEXT
$cpeek :: Ptr DeviceMemoryReportEventTypeEXT
-> IO DeviceMemoryReportEventTypeEXT
pokeByteOff :: Ptr b -> Int -> DeviceMemoryReportEventTypeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DeviceMemoryReportEventTypeEXT -> IO ()
peekByteOff :: Ptr b -> Int -> IO DeviceMemoryReportEventTypeEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DeviceMemoryReportEventTypeEXT
pokeElemOff :: Ptr DeviceMemoryReportEventTypeEXT
-> Int -> DeviceMemoryReportEventTypeEXT -> IO ()
$cpokeElemOff :: Ptr DeviceMemoryReportEventTypeEXT
-> Int -> DeviceMemoryReportEventTypeEXT -> IO ()
peekElemOff :: Ptr DeviceMemoryReportEventTypeEXT
-> Int -> IO DeviceMemoryReportEventTypeEXT
$cpeekElemOff :: Ptr DeviceMemoryReportEventTypeEXT
-> Int -> IO DeviceMemoryReportEventTypeEXT
alignment :: DeviceMemoryReportEventTypeEXT -> Int
$calignment :: DeviceMemoryReportEventTypeEXT -> Int
sizeOf :: DeviceMemoryReportEventTypeEXT -> Int
$csizeOf :: DeviceMemoryReportEventTypeEXT -> Int
Storable, DeviceMemoryReportEventTypeEXT
DeviceMemoryReportEventTypeEXT
-> Zero DeviceMemoryReportEventTypeEXT
forall a. a -> Zero a
zero :: DeviceMemoryReportEventTypeEXT
$czero :: DeviceMemoryReportEventTypeEXT
Zero)

-- | 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT' specifies this event
-- corresponds to the allocation of an internal device memory object or a
-- 'Vulkan.Core10.Handles.DeviceMemory'.
pattern $bDEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT :: DeviceMemoryReportEventTypeEXT
$mDEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT :: forall r.
DeviceMemoryReportEventTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT          = DeviceMemoryReportEventTypeEXT 0
-- | 'DEVICE_MEMORY_REPORT_EVENT_TYPE_FREE_EXT' specifies this event
-- corresponds to the deallocation of an internally-allocated device memory
-- object or a 'Vulkan.Core10.Handles.DeviceMemory'.
pattern $bDEVICE_MEMORY_REPORT_EVENT_TYPE_FREE_EXT :: DeviceMemoryReportEventTypeEXT
$mDEVICE_MEMORY_REPORT_EVENT_TYPE_FREE_EXT :: forall r.
DeviceMemoryReportEventTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEVICE_MEMORY_REPORT_EVENT_TYPE_FREE_EXT              = DeviceMemoryReportEventTypeEXT 1
-- | 'DEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT' specifies this event
-- corresponds to the import of an external memory object.
pattern $bDEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT :: DeviceMemoryReportEventTypeEXT
$mDEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT :: forall r.
DeviceMemoryReportEventTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT            = DeviceMemoryReportEventTypeEXT 2
-- | 'DEVICE_MEMORY_REPORT_EVENT_TYPE_UNIMPORT_EXT' specifies this event is
-- the release of an imported external memory object.
pattern $bDEVICE_MEMORY_REPORT_EVENT_TYPE_UNIMPORT_EXT :: DeviceMemoryReportEventTypeEXT
$mDEVICE_MEMORY_REPORT_EVENT_TYPE_UNIMPORT_EXT :: forall r.
DeviceMemoryReportEventTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEVICE_MEMORY_REPORT_EVENT_TYPE_UNIMPORT_EXT          = DeviceMemoryReportEventTypeEXT 3
-- | 'DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT' specifies this
-- event corresponds to the failed allocation of an internal device memory
-- object or a 'Vulkan.Core10.Handles.DeviceMemory'.
pattern $bDEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT :: DeviceMemoryReportEventTypeEXT
$mDEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT :: forall r.
DeviceMemoryReportEventTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT = DeviceMemoryReportEventTypeEXT 4
{-# complete DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT,
             DEVICE_MEMORY_REPORT_EVENT_TYPE_FREE_EXT,
             DEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT,
             DEVICE_MEMORY_REPORT_EVENT_TYPE_UNIMPORT_EXT,
             DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT :: DeviceMemoryReportEventTypeEXT #-}

conNameDeviceMemoryReportEventTypeEXT :: String
conNameDeviceMemoryReportEventTypeEXT :: String
conNameDeviceMemoryReportEventTypeEXT = String
"DeviceMemoryReportEventTypeEXT"

enumPrefixDeviceMemoryReportEventTypeEXT :: String
enumPrefixDeviceMemoryReportEventTypeEXT :: String
enumPrefixDeviceMemoryReportEventTypeEXT = String
"DEVICE_MEMORY_REPORT_EVENT_TYPE_"

showTableDeviceMemoryReportEventTypeEXT :: [(DeviceMemoryReportEventTypeEXT, String)]
showTableDeviceMemoryReportEventTypeEXT :: [(DeviceMemoryReportEventTypeEXT, String)]
showTableDeviceMemoryReportEventTypeEXT =
  [ (DeviceMemoryReportEventTypeEXT
DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATE_EXT         , String
"ALLOCATE_EXT")
  , (DeviceMemoryReportEventTypeEXT
DEVICE_MEMORY_REPORT_EVENT_TYPE_FREE_EXT             , String
"FREE_EXT")
  , (DeviceMemoryReportEventTypeEXT
DEVICE_MEMORY_REPORT_EVENT_TYPE_IMPORT_EXT           , String
"IMPORT_EXT")
  , (DeviceMemoryReportEventTypeEXT
DEVICE_MEMORY_REPORT_EVENT_TYPE_UNIMPORT_EXT         , String
"UNIMPORT_EXT")
  , (DeviceMemoryReportEventTypeEXT
DEVICE_MEMORY_REPORT_EVENT_TYPE_ALLOCATION_FAILED_EXT, String
"ALLOCATION_FAILED_EXT")
  ]

instance Show DeviceMemoryReportEventTypeEXT where
  showsPrec :: Int -> DeviceMemoryReportEventTypeEXT -> ShowS
showsPrec = String
-> [(DeviceMemoryReportEventTypeEXT, String)]
-> String
-> (DeviceMemoryReportEventTypeEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> DeviceMemoryReportEventTypeEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec String
enumPrefixDeviceMemoryReportEventTypeEXT
                            [(DeviceMemoryReportEventTypeEXT, String)]
showTableDeviceMemoryReportEventTypeEXT
                            String
conNameDeviceMemoryReportEventTypeEXT
                            (\(DeviceMemoryReportEventTypeEXT Int32
x) -> Int32
x)
                            (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read DeviceMemoryReportEventTypeEXT where
  readPrec :: ReadPrec DeviceMemoryReportEventTypeEXT
readPrec = String
-> [(DeviceMemoryReportEventTypeEXT, String)]
-> String
-> (Int32 -> DeviceMemoryReportEventTypeEXT)
-> ReadPrec DeviceMemoryReportEventTypeEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec String
enumPrefixDeviceMemoryReportEventTypeEXT
                          [(DeviceMemoryReportEventTypeEXT, String)]
showTableDeviceMemoryReportEventTypeEXT
                          String
conNameDeviceMemoryReportEventTypeEXT
                          Int32 -> DeviceMemoryReportEventTypeEXT
DeviceMemoryReportEventTypeEXT


type FN_vkDeviceMemoryReportCallbackEXT = ("pCallbackData" ::: Ptr DeviceMemoryReportCallbackDataEXT) -> ("pUserData" ::: Ptr ()) -> IO ()
-- | PFN_vkDeviceMemoryReportCallbackEXT - Application-defined device memory
-- report callback function
--
-- = Description
--
-- The callback /must/ not make calls to any Vulkan commands.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_device_memory_report VK_EXT_device_memory_report>,
-- 'DeviceDeviceMemoryReportCreateInfoEXT'
type PFN_vkDeviceMemoryReportCallbackEXT = FunPtr FN_vkDeviceMemoryReportCallbackEXT


type EXT_DEVICE_MEMORY_REPORT_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_DEVICE_MEMORY_REPORT_SPEC_VERSION"
pattern EXT_DEVICE_MEMORY_REPORT_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_DEVICE_MEMORY_REPORT_SPEC_VERSION :: a
$mEXT_DEVICE_MEMORY_REPORT_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
EXT_DEVICE_MEMORY_REPORT_SPEC_VERSION = 2


type EXT_DEVICE_MEMORY_REPORT_EXTENSION_NAME = "VK_EXT_device_memory_report"

-- No documentation found for TopLevel "VK_EXT_DEVICE_MEMORY_REPORT_EXTENSION_NAME"
pattern EXT_DEVICE_MEMORY_REPORT_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_DEVICE_MEMORY_REPORT_EXTENSION_NAME :: a
$mEXT_DEVICE_MEMORY_REPORT_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_DEVICE_MEMORY_REPORT_EXTENSION_NAME = "VK_EXT_device_memory_report"