{-# language CPP #-}
-- | = Name
--
-- VK_EXT_opacity_micromap - device extension
--
-- == VK_EXT_opacity_micromap
--
-- [__Name String__]
--     @VK_EXT_opacity_micromap@
--
-- [__Extension Type__]
--     Device extension
--
-- [__Registered Extension Number__]
--     397
--
-- [__Revision__]
--     2
--
-- [__Extension and Version Dependencies__]
--
--     -   Requires support for Vulkan 1.0
--
--     -   Requires @VK_KHR_acceleration_structure@ to be enabled for any
--         device-level functionality
--
--     -   Requires @VK_KHR_synchronization2@ to be enabled for any
--         device-level functionality
--
-- [__Contact__]
--
--     -   Christoph Kubisch
--         <https://github.com/KhronosGroup/Vulkan-Docs/issues/new?body=[VK_EXT_opacity_micromap] @pixeljetstream%0A*Here describe the issue or question you have about the VK_EXT_opacity_micromap extension* >
--
--     -   Eric Werness
--
-- [__Extension Proposal__]
--     <https://github.com/KhronosGroup/Vulkan-Docs/tree/main/proposals/VK_EXT_opacity_micromap.adoc VK_EXT_opacity_micromap>
--
-- == Other Extension Metadata
--
-- [__Last Modified Date__]
--     2022-08-24
--
-- [__Interactions and External Dependencies__]
--
--     -   This extension requires
--         <https://htmlpreview.github.io/?https://github.com/KhronosGroup/SPIRV-Registry/blob/master/extensions/EXT/SPV_EXT_ray_tracing_opacity_micromap.html SPV_EXT_ray_tracing_opacity_micromap>
--
--     -   This extension provides API support for
--         <https://github.com/KhronosGroup/GLSL/blob/master/extensions/EXT/GLSL_EXT_ray_tracing_opacity_micromap.txt GLSL_EXT_ray_tracing_opacity_micromap>
--
-- [__Contributors__]
--
--     -   Christoph Kubisch, NVIDIA
--
--     -   Eric Werness, NVIDIA
--
--     -   Josh Barczak, Intel
--
--     -   Stu Smith, AMD
--
-- == Description
--
-- When adding adding transparency to a ray traced scene, an application
-- can choose between further tessellating the geometry or using an any hit
-- shader to allow the ray through specific parts of the geometry. These
-- options have the downside of either significantly increasing memory
-- consumption or adding runtime overhead to run shader code in the middle
-- of traversal, respectively.
--
-- This extension adds the ability to add an /opacity micromap/ to geometry
-- when building an acceleration structure. The opacity micromap compactly
-- encodes opacity information which can be read by the implementation to
-- mark parts of triangles as opaque or transparent. The format is
-- externally visible to allow the application to compress its internal
-- geometry and surface representations into the compressed format ahead of
-- time. The compressed format subdivides each triangle into a set of
-- subtriangles, each of which can be assigned either two or four opacity
-- values. These opacity values can control if a ray hitting that
-- subtriangle is treated as an opaque hit, complete miss, or possible hit,
-- depending on the controls described in
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#ray-opacity-micromap Ray Opacity Micromap>.
--
-- This extension provides:
--
-- -   a 'Vulkan.Extensions.Handles.MicromapEXT' structure to store the
--     micromap,
--
-- -   functions similar to acceleration structure build functions to build
--     the opacity micromap array, and
--
-- -   a structure to extend
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.AccelerationStructureGeometryTrianglesDataKHR'
--     to attach a micromap to the geometry of the acceleration structure.
--
-- == New Object Types
--
-- -   'Vulkan.Extensions.Handles.MicromapEXT'
--
-- == New Commands
--
-- -   'buildMicromapsEXT'
--
-- -   'cmdBuildMicromapsEXT'
--
-- -   'cmdCopyMemoryToMicromapEXT'
--
-- -   'cmdCopyMicromapEXT'
--
-- -   'cmdCopyMicromapToMemoryEXT'
--
-- -   'cmdWriteMicromapsPropertiesEXT'
--
-- -   'copyMemoryToMicromapEXT'
--
-- -   'copyMicromapEXT'
--
-- -   'copyMicromapToMemoryEXT'
--
-- -   'createMicromapEXT'
--
-- -   'destroyMicromapEXT'
--
-- -   'getDeviceMicromapCompatibilityEXT'
--
-- -   'getMicromapBuildSizesEXT'
--
-- -   'writeMicromapsPropertiesEXT'
--
-- == New Structures
--
-- -   'CopyMemoryToMicromapInfoEXT'
--
-- -   'CopyMicromapInfoEXT'
--
-- -   'CopyMicromapToMemoryInfoEXT'
--
-- -   'MicromapBuildInfoEXT'
--
-- -   'MicromapBuildSizesInfoEXT'
--
-- -   'MicromapCreateInfoEXT'
--
-- -   'MicromapTriangleEXT'
--
-- -   'MicromapUsageEXT'
--
-- -   'MicromapVersionInfoEXT'
--
-- -   Extending
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.AccelerationStructureGeometryTrianglesDataKHR':
--
--     -   'AccelerationStructureTrianglesOpacityMicromapEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
--     'Vulkan.Core10.Device.DeviceCreateInfo':
--
--     -   'PhysicalDeviceOpacityMicromapFeaturesEXT'
--
-- -   Extending
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2':
--
--     -   'PhysicalDeviceOpacityMicromapPropertiesEXT'
--
-- == New Enums
--
-- -   'BuildMicromapFlagBitsEXT'
--
-- -   'BuildMicromapModeEXT'
--
-- -   'CopyMicromapModeEXT'
--
-- -   'MicromapCreateFlagBitsEXT'
--
-- -   'MicromapTypeEXT'
--
-- -   'OpacityMicromapFormatEXT'
--
-- -   'OpacityMicromapSpecialIndexEXT'
--
-- == New Bitmasks
--
-- -   'BuildMicromapFlagsEXT'
--
-- -   'MicromapCreateFlagsEXT'
--
-- == New Enum Constants
--
-- -   'EXT_OPACITY_MICROMAP_EXTENSION_NAME'
--
-- -   'EXT_OPACITY_MICROMAP_SPEC_VERSION'
--
-- -   Extending 'Vulkan.Core13.Enums.AccessFlags2.AccessFlagBits2':
--
--     -   'Vulkan.Core13.Enums.AccessFlags2.ACCESS_2_MICROMAP_READ_BIT_EXT'
--
--     -   'Vulkan.Core13.Enums.AccessFlags2.ACCESS_2_MICROMAP_WRITE_BIT_EXT'
--
-- -   Extending
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BufferUsageFlagBits':
--
--     -   'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_MICROMAP_BUILD_INPUT_READ_ONLY_BIT_EXT'
--
--     -   'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_MICROMAP_STORAGE_BIT_EXT'
--
-- -   Extending
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.BuildAccelerationStructureFlagBitsKHR':
--
--     -   'Vulkan.Extensions.VK_KHR_acceleration_structure.BUILD_ACCELERATION_STRUCTURE_ALLOW_DISABLE_OPACITY_MICROMAPS_EXT'
--
--     -   'Vulkan.Extensions.VK_KHR_acceleration_structure.BUILD_ACCELERATION_STRUCTURE_ALLOW_OPACITY_MICROMAP_DATA_UPDATE_EXT'
--
--     -   'Vulkan.Extensions.VK_KHR_acceleration_structure.BUILD_ACCELERATION_STRUCTURE_ALLOW_OPACITY_MICROMAP_UPDATE_EXT'
--
-- -   Extending
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.GeometryInstanceFlagBitsKHR':
--
--     -   'Vulkan.Extensions.VK_KHR_acceleration_structure.GEOMETRY_INSTANCE_DISABLE_OPACITY_MICROMAPS_EXT'
--
--     -   'Vulkan.Extensions.VK_KHR_acceleration_structure.GEOMETRY_INSTANCE_FORCE_OPACITY_MICROMAP_2_STATE_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.ObjectType.ObjectType':
--
--     -   'Vulkan.Core10.Enums.ObjectType.OBJECT_TYPE_MICROMAP_EXT'
--
-- -   Extending
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlagBits':
--
--     -   'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_OPACITY_MICROMAP_BIT_EXT'
--
-- -   Extending
--     'Vulkan.Core13.Enums.PipelineStageFlags2.PipelineStageFlagBits2':
--
--     -   'Vulkan.Core13.Enums.PipelineStageFlags2.PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.QueryType.QueryType':
--
--     -   'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_COMPACTED_SIZE_EXT'
--
--     -   'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_SERIALIZATION_SIZE_EXT'
--
-- -   Extending 'Vulkan.Core10.Enums.StructureType.StructureType':
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ACCELERATION_STRUCTURE_TRIANGLES_OPACITY_MICROMAP_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COPY_MEMORY_TO_MICROMAP_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COPY_MICROMAP_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COPY_MICROMAP_TO_MEMORY_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MICROMAP_BUILD_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MICROMAP_BUILD_SIZES_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MICROMAP_CREATE_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MICROMAP_VERSION_INFO_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_OPACITY_MICROMAP_FEATURES_EXT'
--
--     -   'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_OPACITY_MICROMAP_PROPERTIES_EXT'
--
-- == Reference code
--
-- > uint32_t BarycentricsToSpaceFillingCurveIndex(float u, float v, uint32_t level)
-- > {
-- >     u = clamp(u, 0.0f, 1.0f);
-- >     v = clamp(v, 0.0f, 1.0f);
-- >
-- >     uint32_t iu, iv, iw;
-- >
-- >     // Quantize barycentric coordinates
-- >     float fu = u * (1u << level);
-- >     float fv = v * (1u << level);
-- >
-- >     iu = (uint32_t)fu;
-- >     iv = (uint32_t)fv;
-- >
-- >     float uf = fu - float(iu);
-- >     float vf = fv - float(iv);
-- >
-- >     if (iu >= (1u << level)) iu = (1u << level) - 1u;
-- >     if (iv >= (1u << level)) iv = (1u << level) - 1u;
-- >
-- >     uint32_t iuv = iu + iv;
-- >
-- >     if (iuv >= (1u << level))
-- >         iu -= iuv - (1u << level) + 1u;
-- >
-- >     iw = ~(iu + iv);
-- >
-- >     if (uf + vf >= 1.0f && iuv < (1u link:https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html# level) - 1u) --iw;
-- >
-- >     uint32_t b0 = ~(iu ^ iw);
-- >     b0 &= ((1u << level) - 1u);
-- >     uint32_t t = (iu ^ iv) & b0;
-- >
-- >     uint32_t f = t;
-- >     f ^= f [^] 1u;
-- >     f ^= f >> 2u;
-- >     f ^= f >> 4u;
-- >     f ^= f >> 8u;
-- >     uint32_t b1 = ((f ^ iu) & ~b0) | t;
-- >
-- >     // Interleave bits
-- >     b0 = (b0 | (b0 << 8u)) & 0x00ff00ffu;
-- >     b0 = (b0 | (b0 << 4u)) & 0x0f0f0f0fu;
-- >     b0 = (b0 | (b0 << 2u)) & 0x33333333u;
-- >     b0 = (b0 | (b0 << 1u)) & 0x55555555u;
-- >     b1 = (b1 | (b1 << 8u)) & 0x00ff00ffu;
-- >     b1 = (b1 | (b1 << 4u)) & 0x0f0f0f0fu;
-- >     b1 = (b1 | (b1 << 2u)) & 0x33333333u;
-- >     b1 = (b1 | (b1 << 1u)) & 0x55555555u;
-- >
-- >     return b0 | (b1 << 1u);
-- > }
--
-- == Issues
--
-- (1) Is the build actually similar to an acceleration structure build?
--
-- -   Resolved: The build should be much lighter-weight than an
--     acceleration structure build, but the infrastructure is similar
--     enough that it makes sense to keep the concepts compatible.
--
-- (2) Why does VkMicromapUsageEXT not have type\/pNext?
--
-- -   Resolved: There can be a very large number of these structures, so
--     doubling the size of these can be significant memory consumption.
--     Also, an application may be loading these directly from a file which
--     is more compatible with it being a flat structure. The including
--     structures are extensible and are probably a more suitable place to
--     add extensibility.
--
-- (3) Why is there a SPIR-V extension?
--
-- -   Resolved: There is a ray flag. To be consistent with how the
--     existing ray tracing extensions work that ray flag needs its own
--     extension.
--
-- (4) Should there be indirect micromap build?
--
-- -   Resolved: Not for now. There is more in-depth usage metadata
--     required and it seems less likely that something like a GPU culling
--     system would need to change the counts for a micromap.
--
-- (5) Should micromaps have a micromap device address?
--
-- -   Resolved: There is no need right now (can just use the handle) but
--     that is a bit different from acceleration structures, though the two
--     are not completely parallel in their usage.
--
-- (6) Why are the alignment requirements defined as a mix of hardcoded
-- values and caps?
--
-- -   Resolved: This is most parallel with the definition of
--     @VK_KHR_acceleration_structure@ and maintaining commonality makes it
--     easier for applications to share memory.
--
-- == Version History
--
-- -   Revision 2, 2022-06-22 (Eric Werness)
--
--     -   EXTify and clean up for discussion
--
-- -   Revision 1, 2022-01-01 (Eric Werness)
--
--     -   Initial revision
--
-- == See Also
--
-- 'AccelerationStructureTrianglesOpacityMicromapEXT',
-- 'BuildMicromapFlagBitsEXT', 'BuildMicromapFlagsEXT',
-- 'BuildMicromapModeEXT', 'CopyMemoryToMicromapInfoEXT',
-- 'CopyMicromapInfoEXT', 'CopyMicromapModeEXT',
-- 'CopyMicromapToMemoryInfoEXT', 'MicromapBuildInfoEXT',
-- 'MicromapBuildSizesInfoEXT', 'MicromapCreateFlagBitsEXT',
-- 'MicromapCreateFlagsEXT', 'MicromapCreateInfoEXT',
-- 'Vulkan.Extensions.Handles.MicromapEXT', 'MicromapTriangleEXT',
-- 'MicromapTypeEXT', 'MicromapUsageEXT', 'MicromapVersionInfoEXT',
-- 'OpacityMicromapFormatEXT', 'OpacityMicromapSpecialIndexEXT',
-- 'PhysicalDeviceOpacityMicromapFeaturesEXT',
-- 'PhysicalDeviceOpacityMicromapPropertiesEXT', 'buildMicromapsEXT',
-- 'cmdBuildMicromapsEXT', 'cmdCopyMemoryToMicromapEXT',
-- 'cmdCopyMicromapEXT', 'cmdCopyMicromapToMemoryEXT',
-- 'cmdWriteMicromapsPropertiesEXT', 'copyMemoryToMicromapEXT',
-- 'copyMicromapEXT', 'copyMicromapToMemoryEXT', 'createMicromapEXT',
-- 'destroyMicromapEXT', 'getDeviceMicromapCompatibilityEXT',
-- 'getMicromapBuildSizesEXT', 'writeMicromapsPropertiesEXT'
--
-- == Document Notes
--
-- For more information, see the
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#VK_EXT_opacity_micromap 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_opacity_micromap  ( createMicromapEXT
                                                  , withMicromapEXT
                                                  , cmdBuildMicromapsEXT
                                                  , buildMicromapsEXT
                                                  , destroyMicromapEXT
                                                  , cmdCopyMicromapEXT
                                                  , copyMicromapEXT
                                                  , cmdCopyMicromapToMemoryEXT
                                                  , copyMicromapToMemoryEXT
                                                  , cmdCopyMemoryToMicromapEXT
                                                  , copyMemoryToMicromapEXT
                                                  , cmdWriteMicromapsPropertiesEXT
                                                  , writeMicromapsPropertiesEXT
                                                  , getDeviceMicromapCompatibilityEXT
                                                  , getMicromapBuildSizesEXT
                                                  , MicromapBuildInfoEXT(..)
                                                  , MicromapCreateInfoEXT(..)
                                                  , MicromapVersionInfoEXT(..)
                                                  , CopyMicromapInfoEXT(..)
                                                  , CopyMicromapToMemoryInfoEXT(..)
                                                  , CopyMemoryToMicromapInfoEXT(..)
                                                  , MicromapBuildSizesInfoEXT(..)
                                                  , MicromapUsageEXT(..)
                                                  , MicromapTriangleEXT(..)
                                                  , PhysicalDeviceOpacityMicromapFeaturesEXT(..)
                                                  , PhysicalDeviceOpacityMicromapPropertiesEXT(..)
                                                  , AccelerationStructureTrianglesOpacityMicromapEXT(..)
                                                  , MicromapTypeEXT( MICROMAP_TYPE_OPACITY_MICROMAP_EXT
                                                                   , ..
                                                                   )
                                                  , BuildMicromapFlagsEXT
                                                  , BuildMicromapFlagBitsEXT( BUILD_MICROMAP_PREFER_FAST_TRACE_BIT_EXT
                                                                            , BUILD_MICROMAP_PREFER_FAST_BUILD_BIT_EXT
                                                                            , BUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT
                                                                            , ..
                                                                            )
                                                  , MicromapCreateFlagsEXT
                                                  , MicromapCreateFlagBitsEXT( MICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT
                                                                             , ..
                                                                             )
                                                  , CopyMicromapModeEXT( COPY_MICROMAP_MODE_CLONE_EXT
                                                                       , COPY_MICROMAP_MODE_SERIALIZE_EXT
                                                                       , COPY_MICROMAP_MODE_DESERIALIZE_EXT
                                                                       , COPY_MICROMAP_MODE_COMPACT_EXT
                                                                       , ..
                                                                       )
                                                  , BuildMicromapModeEXT( BUILD_MICROMAP_MODE_BUILD_EXT
                                                                        , ..
                                                                        )
                                                  , OpacityMicromapFormatEXT( OPACITY_MICROMAP_FORMAT_2_STATE_EXT
                                                                            , OPACITY_MICROMAP_FORMAT_4_STATE_EXT
                                                                            , ..
                                                                            )
                                                  , OpacityMicromapSpecialIndexEXT( OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_TRANSPARENT_EXT
                                                                                  , OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_OPAQUE_EXT
                                                                                  , OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_TRANSPARENT_EXT
                                                                                  , OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_OPAQUE_EXT
                                                                                  , ..
                                                                                  )
                                                  , EXT_OPACITY_MICROMAP_SPEC_VERSION
                                                  , pattern EXT_OPACITY_MICROMAP_SPEC_VERSION
                                                  , EXT_OPACITY_MICROMAP_EXTENSION_NAME
                                                  , pattern EXT_OPACITY_MICROMAP_EXTENSION_NAME
                                                  , DeferredOperationKHR(..)
                                                  , MicromapEXT(..)
                                                  , DeviceOrHostAddressKHR(..)
                                                  , DeviceOrHostAddressConstKHR(..)
                                                  , GeometryInstanceFlagBitsKHR(..)
                                                  , GeometryInstanceFlagsKHR
                                                  , BuildAccelerationStructureFlagBitsKHR(..)
                                                  , BuildAccelerationStructureFlagsKHR
                                                  , AccelerationStructureBuildTypeKHR(..)
                                                  , AccelerationStructureCompatibilityKHR(..)
                                                  ) where

import Vulkan.Internal.Utils (enumReadPrec)
import Vulkan.Internal.Utils (enumShowsPrec)
import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytes)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Numeric (showHex)
import qualified Data.ByteString (length)
import Data.ByteString (packCStringLen)
import Data.ByteString.Unsafe (unsafeUseAsCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import qualified Data.Vector (null)
import Foreign.C.Types (CSize(..))
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 Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
import Data.Bits (FiniteBits)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CSize)
import Foreign.C.Types (CSize(CSize))
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 Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import GHC.Show (Show(showsPrec))
import Data.Word (Word16)
import Data.Word (Word32)
import Data.Word (Word64)
import Data.Word (Word8)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.NamedType ((:::))
import Vulkan.Extensions.VK_KHR_acceleration_structure (AccelerationStructureBuildTypeKHR)
import Vulkan.Extensions.VK_KHR_acceleration_structure (AccelerationStructureBuildTypeKHR(..))
import Vulkan.Extensions.VK_KHR_acceleration_structure (AccelerationStructureCompatibilityKHR)
import Vulkan.Extensions.VK_KHR_acceleration_structure (AccelerationStructureCompatibilityKHR(..))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer(CommandBuffer))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Extensions.Handles (DeferredOperationKHR)
import Vulkan.Extensions.Handles (DeferredOperationKHR(..))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Core10.FundamentalTypes (DeviceAddress)
import Vulkan.Dynamic (DeviceCmds(pVkBuildMicromapsEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBuildMicromapsEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyMemoryToMicromapEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyMicromapEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyMicromapToMemoryEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCmdWriteMicromapsPropertiesEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCopyMemoryToMicromapEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCopyMicromapEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCopyMicromapToMemoryEXT))
import Vulkan.Dynamic (DeviceCmds(pVkCreateMicromapEXT))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyMicromapEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceMicromapCompatibilityEXT))
import Vulkan.Dynamic (DeviceCmds(pVkGetMicromapBuildSizesEXT))
import Vulkan.Dynamic (DeviceCmds(pVkWriteMicromapsPropertiesEXT))
import Vulkan.Extensions.VK_KHR_acceleration_structure (DeviceOrHostAddressConstKHR)
import Vulkan.Extensions.VK_KHR_acceleration_structure (DeviceOrHostAddressKHR)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Enums.IndexType (IndexType)
import Vulkan.Extensions.Handles (MicromapEXT)
import Vulkan.Extensions.Handles (MicromapEXT(..))
import Vulkan.Core10.Handles (QueryPool)
import Vulkan.Core10.Handles (QueryPool(..))
import Vulkan.Core10.Enums.QueryType (QueryType)
import Vulkan.Core10.Enums.QueryType (QueryType(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_TRIANGLES_OPACITY_MICROMAP_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COPY_MEMORY_TO_MICROMAP_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COPY_MICROMAP_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COPY_MICROMAP_TO_MEMORY_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MICROMAP_BUILD_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MICROMAP_BUILD_SIZES_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MICROMAP_CREATE_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MICROMAP_VERSION_INFO_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_OPACITY_MICROMAP_FEATURES_EXT))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_OPACITY_MICROMAP_PROPERTIES_EXT))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.APIConstants (pattern UUID_SIZE)
import Vulkan.Extensions.VK_KHR_acceleration_structure (AccelerationStructureBuildTypeKHR(..))
import Vulkan.Extensions.VK_KHR_acceleration_structure (AccelerationStructureCompatibilityKHR(..))
import Vulkan.Extensions.VK_KHR_acceleration_structure (BuildAccelerationStructureFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_acceleration_structure (BuildAccelerationStructureFlagsKHR)
import Vulkan.Extensions.Handles (DeferredOperationKHR(..))
import Vulkan.Extensions.VK_KHR_acceleration_structure (DeviceOrHostAddressConstKHR(..))
import Vulkan.Extensions.VK_KHR_acceleration_structure (DeviceOrHostAddressKHR(..))
import Vulkan.Extensions.VK_KHR_acceleration_structure (GeometryInstanceFlagBitsKHR(..))
import Vulkan.Extensions.VK_KHR_acceleration_structure (GeometryInstanceFlagsKHR)
import Vulkan.Extensions.Handles (MicromapEXT(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateMicromapEXT
  :: FunPtr (Ptr Device_T -> Ptr MicromapCreateInfoEXT -> Ptr AllocationCallbacks -> Ptr MicromapEXT -> IO Result) -> Ptr Device_T -> Ptr MicromapCreateInfoEXT -> Ptr AllocationCallbacks -> Ptr MicromapEXT -> IO Result

-- | vkCreateMicromapEXT - Create a new micromap object
--
-- = Description
--
-- Similar to other objects in Vulkan, the micromap creation merely creates
-- an object with a specific “shape”. The type and quantity of geometry
-- that can be built into a micromap is determined by the parameters of
-- 'MicromapCreateInfoEXT'.
--
-- Populating the data in the object after allocating and binding memory is
-- done with commands such as 'cmdBuildMicromapsEXT', 'buildMicromapsEXT',
-- 'cmdCopyMicromapEXT', and 'copyMicromapEXT'.
--
-- The input buffers passed to micromap build commands will be referenced
-- by the implementation for the duration of the command. Micromaps /must/
-- be fully self-contained. The application /may/ re-use or free any memory
-- which was used by the command as an input or as scratch without
-- affecting the results of a subsequent acceleration structure build using
-- the micromap or traversal of that acceleration structure.
--
-- == Valid Usage
--
-- -   #VUID-vkCreateMicromapEXT-micromap-07430# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromap micromap>
--     feature /must/ be enabled
--
-- -   #VUID-vkCreateMicromapEXT-deviceAddress-07431# If
--     'MicromapCreateInfoEXT'::@deviceAddress@ is not zero, the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromapCaptureReplay micromapCaptureReplay>
--     feature /must/ be enabled
--
-- -   #VUID-vkCreateMicromapEXT-device-07432# If @device@ was created with
--     multiple physical devices, then the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-bufferDeviceAddressMultiDevice bufferDeviceAddressMultiDevice>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCreateMicromapEXT-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkCreateMicromapEXT-pCreateInfo-parameter# @pCreateInfo@
--     /must/ be a valid pointer to a valid 'MicromapCreateInfoEXT'
--     structure
--
-- -   #VUID-vkCreateMicromapEXT-pAllocator-parameter# If @pAllocator@ is
--     not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   #VUID-vkCreateMicromapEXT-pMicromap-parameter# @pMicromap@ /must/ be
--     a valid pointer to a 'Vulkan.Extensions.Handles.MicromapEXT' handle
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Extensions.VK_KHR_buffer_device_address.ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS_KHR'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'MicromapCreateInfoEXT',
-- 'Vulkan.Extensions.Handles.MicromapEXT'
createMicromapEXT :: forall io
                   . (MonadIO io)
                  => -- | @device@ is the logical device that creates the acceleration structure
                     -- object.
                     Device
                  -> -- | @pCreateInfo@ is a pointer to a 'MicromapCreateInfoEXT' structure
                     -- containing parameters affecting creation of the micromap.
                     MicromapCreateInfoEXT
                  -> -- | @pAllocator@ controls host memory allocation as described in the
                     -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                     -- chapter.
                     ("allocator" ::: Maybe AllocationCallbacks)
                  -> io (MicromapEXT)
createMicromapEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> MicromapCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io MicromapEXT
createMicromapEXT Device
device MicromapCreateInfoEXT
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = IO MicromapEXT -> io MicromapEXT
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MicromapEXT -> io MicromapEXT)
-> (ContT MicromapEXT IO MicromapEXT -> IO MicromapEXT)
-> ContT MicromapEXT IO MicromapEXT
-> io MicromapEXT
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT MicromapEXT IO MicromapEXT -> IO MicromapEXT
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT MicromapEXT IO MicromapEXT -> io MicromapEXT)
-> ContT MicromapEXT IO MicromapEXT -> io MicromapEXT
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateMicromapEXTPtr :: FunPtr
  (Ptr Device_T
   -> Ptr MicromapCreateInfoEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> IO Result)
vkCreateMicromapEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Ptr MicromapCreateInfoEXT
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pMicromap" ::: Ptr MicromapEXT)
      -> IO Result)
pVkCreateMicromapEXT (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT MicromapEXT IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT MicromapEXT IO ())
-> IO () -> ContT MicromapEXT IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Ptr MicromapCreateInfoEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> IO Result)
vkCreateMicromapEXTPtr FunPtr
  (Ptr Device_T
   -> Ptr MicromapCreateInfoEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> Ptr MicromapCreateInfoEXT
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pMicromap" ::: Ptr MicromapEXT)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Ptr MicromapCreateInfoEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkCreateMicromapEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateMicromapEXT' :: Ptr Device_T
-> Ptr MicromapCreateInfoEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMicromap" ::: Ptr MicromapEXT)
-> IO Result
vkCreateMicromapEXT' = FunPtr
  (Ptr Device_T
   -> Ptr MicromapCreateInfoEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> IO Result)
-> Ptr Device_T
-> Ptr MicromapCreateInfoEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMicromap" ::: Ptr MicromapEXT)
-> IO Result
mkVkCreateMicromapEXT FunPtr
  (Ptr Device_T
   -> Ptr MicromapCreateInfoEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> IO Result)
vkCreateMicromapEXTPtr
  Ptr MicromapCreateInfoEXT
pCreateInfo <- ((Ptr MicromapCreateInfoEXT -> IO MicromapEXT) -> IO MicromapEXT)
-> ContT MicromapEXT IO (Ptr MicromapCreateInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr MicromapCreateInfoEXT -> IO MicromapEXT) -> IO MicromapEXT)
 -> ContT MicromapEXT IO (Ptr MicromapCreateInfoEXT))
-> ((Ptr MicromapCreateInfoEXT -> IO MicromapEXT)
    -> IO MicromapEXT)
-> ContT MicromapEXT IO (Ptr MicromapCreateInfoEXT)
forall a b. (a -> b) -> a -> b
$ MicromapCreateInfoEXT
-> (Ptr MicromapCreateInfoEXT -> IO MicromapEXT) -> IO MicromapEXT
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MicromapCreateInfoEXT
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT MicromapEXT IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO MicromapEXT)
 -> IO MicromapEXT)
-> ContT MicromapEXT IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO MicromapEXT)
  -> IO MicromapEXT)
 -> ContT MicromapEXT IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO MicromapEXT)
    -> IO MicromapEXT)
-> ContT MicromapEXT IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO MicromapEXT)
-> IO MicromapEXT
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pMicromap" ::: Ptr MicromapEXT
pPMicromap <- ((("pMicromap" ::: Ptr MicromapEXT) -> IO MicromapEXT)
 -> IO MicromapEXT)
-> ContT MicromapEXT IO ("pMicromap" ::: Ptr MicromapEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMicromap" ::: Ptr MicromapEXT) -> IO MicromapEXT)
  -> IO MicromapEXT)
 -> ContT MicromapEXT IO ("pMicromap" ::: Ptr MicromapEXT))
-> ((("pMicromap" ::: Ptr MicromapEXT) -> IO MicromapEXT)
    -> IO MicromapEXT)
-> ContT MicromapEXT IO ("pMicromap" ::: Ptr MicromapEXT)
forall a b. (a -> b) -> a -> b
$ IO ("pMicromap" ::: Ptr MicromapEXT)
-> (("pMicromap" ::: Ptr MicromapEXT) -> IO ())
-> (("pMicromap" ::: Ptr MicromapEXT) -> IO MicromapEXT)
-> IO MicromapEXT
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @MicromapEXT Int
8) ("pMicromap" ::: Ptr MicromapEXT) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT MicromapEXT IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT MicromapEXT IO Result)
-> IO Result -> ContT MicromapEXT IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateMicromapEXT" (Ptr Device_T
-> Ptr MicromapCreateInfoEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMicromap" ::: Ptr MicromapEXT)
-> IO Result
vkCreateMicromapEXT'
                                                        (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                        Ptr MicromapCreateInfoEXT
pCreateInfo
                                                        "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
                                                        ("pMicromap" ::: Ptr MicromapEXT
pPMicromap))
  IO () -> ContT MicromapEXT IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT MicromapEXT IO ())
-> IO () -> ContT MicromapEXT IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  MicromapEXT
pMicromap <- IO MicromapEXT -> ContT MicromapEXT IO MicromapEXT
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO MicromapEXT -> ContT MicromapEXT IO MicromapEXT)
-> IO MicromapEXT -> ContT MicromapEXT IO MicromapEXT
forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @MicromapEXT "pMicromap" ::: Ptr MicromapEXT
pPMicromap
  MicromapEXT -> ContT MicromapEXT IO MicromapEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MicromapEXT -> ContT MicromapEXT IO MicromapEXT)
-> MicromapEXT -> ContT MicromapEXT IO MicromapEXT
forall a b. (a -> b) -> a -> b
$ (MicromapEXT
pMicromap)

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createMicromapEXT' and 'destroyMicromapEXT'
--
-- To ensure that 'destroyMicromapEXT' is always called: pass
-- 'Control.Exception.bracket' (or the allocate function from your
-- favourite resource management library) as the last argument.
-- To just extract the pair pass '(,)' as the last argument.
--
withMicromapEXT :: forall io r . MonadIO io => Device -> MicromapCreateInfoEXT -> Maybe AllocationCallbacks -> (io MicromapEXT -> (MicromapEXT -> io ()) -> r) -> r
withMicromapEXT :: forall (io :: * -> *) r.
MonadIO io =>
Device
-> MicromapCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io MicromapEXT -> (MicromapEXT -> io ()) -> r)
-> r
withMicromapEXT Device
device MicromapCreateInfoEXT
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator io MicromapEXT -> (MicromapEXT -> io ()) -> r
b =
  io MicromapEXT -> (MicromapEXT -> io ()) -> r
b (Device
-> MicromapCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io MicromapEXT
forall (io :: * -> *).
MonadIO io =>
Device
-> MicromapCreateInfoEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io MicromapEXT
createMicromapEXT Device
device MicromapCreateInfoEXT
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(MicromapEXT
o0) -> Device
-> MicromapEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> MicromapEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyMicromapEXT Device
device MicromapEXT
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdBuildMicromapsEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr MicromapBuildInfoEXT -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr MicromapBuildInfoEXT -> IO ()

-- | vkCmdBuildMicromapsEXT - Build a micromap
--
-- = Description
--
-- The 'cmdBuildMicromapsEXT' command provides the ability to initiate
-- multiple micromaps builds, however there is no ordering or
-- synchronization implied between any of the individual micromap builds.
--
-- Note
--
-- This means that there /cannot/ be any memory aliasing between any
-- micromap memories or scratch memories being used by any of the builds.
--
-- Accesses to the micromap scratch buffers as identified by the
-- 'MicromapBuildInfoEXT'::@scratchData@ buffer device addresses /must/ be
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies synchronized>
-- with the
-- 'Vulkan.Core13.Enums.PipelineStageFlags2.PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT'
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages pipeline stage>
-- and an
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types access type>
-- of 'Vulkan.Core13.Enums.AccessFlags2.ACCESS_2_MICROMAP_READ_BIT_EXT' or
-- 'Vulkan.Core13.Enums.AccessFlags2.ACCESS_2_MICROMAP_WRITE_BIT_EXT'.
-- Similarly for accesses to 'MicromapBuildInfoEXT'::@dstMicromap@.
--
-- Accesses to other input buffers as identified by any used values of
-- 'MicromapBuildInfoEXT'::@data@ or
-- 'MicromapBuildInfoEXT'::@triangleArray@ /must/ be
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies synchronized>
-- with the
-- 'Vulkan.Core13.Enums.PipelineStageFlags2.PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT'
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages pipeline stage>
-- and an
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types access type>
-- of 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_SHADER_READ_BIT'.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-07461# For each @pInfos@[i],
--     @dstMicromap@ /must/ have been created with a value of
--     'MicromapCreateInfoEXT'::@size@ greater than or equal to the memory
--     size required by the build operation, as returned by
--     'getMicromapBuildSizesEXT' with @pBuildInfo@ = @pInfos@[i]
--
-- -   #VUID-vkCmdBuildMicromapsEXT-mode-07462# The @mode@ member of each
--     element of @pInfos@ /must/ be a valid 'BuildMicromapModeEXT' value
--
-- -   #VUID-vkCmdBuildMicromapsEXT-dstMicromap-07463# The @dstMicromap@
--     member of any element of @pInfos@ /must/ be a valid
--     'Vulkan.Extensions.Handles.MicromapEXT' handle
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-07464# For each element of
--     @pInfos@ its @type@ member /must/ match the value of
--     'MicromapCreateInfoEXT'::@type@ when its @dstMicromap@ was created
--
-- -   #VUID-vkCmdBuildMicromapsEXT-dstMicromap-07465# The range of memory
--     backing the @dstMicromap@ member of any element of @pInfos@ that is
--     accessed by this command /must/ not overlap the memory backing the
--     @dstMicromap@ member of any other element of @pInfos@, which is
--     accessed by this command
--
-- -   #VUID-vkCmdBuildMicromapsEXT-dstMicromap-07466# The range of memory
--     backing the @dstMicromap@ member of any element of @pInfos@ that is
--     accessed by this command /must/ not overlap the memory backing the
--     @scratchData@ member of any element of @pInfos@ (including the same
--     element), which is accessed by this command
--
-- -   #VUID-vkCmdBuildMicromapsEXT-scratchData-07467# The range of memory
--     backing the @scratchData@ member of any element of @pInfos@ that is
--     accessed by this command /must/ not overlap the memory backing the
--     @scratchData@ member of any other element of @pInfos@, which is
--     accessed by this command
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-07508# For each element of
--     @pInfos@, the @buffer@ used to create its @dstMicromap@ member
--     /must/ be bound to device memory
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-07509# If @pInfos@[i].@mode@ is
--     'BUILD_MICROMAP_MODE_BUILD_EXT', all addresses between
--     @pInfos@[i].@scratchData.deviceAddress@ and
--     @pInfos@[i].@scratchData.deviceAddress@ + N - 1 /must/ be in the
--     buffer device address range of the same buffer, where N is given by
--     the @buildScratchSize@ member of the 'MicromapBuildSizesInfoEXT'
--     structure returned from a call to 'getMicromapBuildSizesEXT' with an
--     identical 'MicromapBuildInfoEXT' structure and primitive count
--
-- -   #VUID-vkCmdBuildMicromapsEXT-data-07510# The buffers from which the
--     buffer device addresses for all of the @data@ and @triangleArray@
--     members of all @pInfos@[i] are queried /must/ have been created with
--     the
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_MICROMAP_BUILD_INPUT_READ_ONLY_BIT_EXT'
--     usage flag
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-07511# For each element of
--     @pInfos@[i] the buffer from which the buffer device address
--     @pInfos@[i].@scratchData.deviceAddress@ is queried /must/ have been
--     created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_STORAGE_BUFFER_BIT'
--     usage flag
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-07512# For each element of
--     @pInfos@, its @scratchData.deviceAddress@, @data.deviceAddress@, and
--     @triangleArray.deviceAddress@ members /must/ be valid device
--     addresses obtained from
--     'Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address.getBufferDeviceAddress'
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-07513# For each element of
--     @pInfos@, if @scratchData.deviceAddress@, @data.deviceAddress@, or
--     @triangleArray.deviceAddress@ is the address of a non-sparse buffer
--     then it /must/ be bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-07514# For each element of
--     @pInfos@, its @scratchData.deviceAddress@ member /must/ be a
--     multiple of
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.PhysicalDeviceAccelerationStructurePropertiesKHR'::@minAccelerationStructureScratchOffsetAlignment@
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-07515# For each element of
--     @pInfos@, its @triangleArray.deviceAddress@ and @data.deviceAddress@
--     members /must/ be a multiple of @256@
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdBuildMicromapsEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdBuildMicromapsEXT-pInfos-parameter# @pInfos@ /must/ be a
--     valid pointer to an array of @infoCount@ valid
--     'MicromapBuildInfoEXT' structures
--
-- -   #VUID-vkCmdBuildMicromapsEXT-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdBuildMicromapsEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   #VUID-vkCmdBuildMicromapsEXT-renderpass# This command /must/ only be
--     called outside of a render pass instance
--
-- -   #VUID-vkCmdBuildMicromapsEXT-videocoding# This command /must/ only
--     be called outside of a video coding scope
--
-- -   #VUID-vkCmdBuildMicromapsEXT-infoCount-arraylength# @infoCount@
--     /must/ be greater than @0@
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Outside                                                                                                                     | Compute                                                                                                               | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             |                                                                                                                       |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'MicromapBuildInfoEXT'
cmdBuildMicromapsEXT :: forall io
                      . (MonadIO io)
                     => -- | @commandBuffer@ is the command buffer into which the command will be
                        -- recorded.
                        CommandBuffer
                     -> -- | @pInfos@ is a pointer to an array of @infoCount@ 'MicromapBuildInfoEXT'
                        -- structures defining the data used to build each micromap.
                        ("infos" ::: Vector MicromapBuildInfoEXT)
                     -> io ()
cmdBuildMicromapsEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> ("infos" ::: Vector MicromapBuildInfoEXT) -> io ()
cmdBuildMicromapsEXT CommandBuffer
commandBuffer "infos" ::: Vector MicromapBuildInfoEXT
infos = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdBuildMicromapsEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ())
vkCmdBuildMicromapsEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ())
pVkCmdBuildMicromapsEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ())
vkCmdBuildMicromapsEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ())
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkCmdBuildMicromapsEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBuildMicromapsEXT' :: Ptr CommandBuffer_T
-> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ()
vkCmdBuildMicromapsEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ())
-> Ptr CommandBuffer_T
-> Flags
-> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> IO ()
mkVkCmdBuildMicromapsEXT FunPtr
  (Ptr CommandBuffer_T
   -> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ())
vkCmdBuildMicromapsEXTPtr
  "pInfos" ::: Ptr MicromapBuildInfoEXT
pPInfos <- ((("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ()) -> IO ())
-> ContT () IO ("pInfos" ::: Ptr MicromapBuildInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ()) -> IO ())
 -> ContT () IO ("pInfos" ::: Ptr MicromapBuildInfoEXT))
-> ((("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ()) -> IO ())
-> ContT () IO ("pInfos" ::: Ptr MicromapBuildInfoEXT)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @MicromapBuildInfoEXT ((("infos" ::: Vector MicromapBuildInfoEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length ("infos" ::: Vector MicromapBuildInfoEXT
infos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
96)
  (Int -> MicromapBuildInfoEXT -> ContT () IO ())
-> ("infos" ::: Vector MicromapBuildInfoEXT) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i MicromapBuildInfoEXT
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> MicromapBuildInfoEXT -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pInfos" ::: Ptr MicromapBuildInfoEXT
pPInfos ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> "pInfos" ::: Ptr MicromapBuildInfoEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
96 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MicromapBuildInfoEXT) (MicromapBuildInfoEXT
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("infos" ::: Vector MicromapBuildInfoEXT
infos)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdBuildMicromapsEXT" (Ptr CommandBuffer_T
-> Flags -> ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO ()
vkCmdBuildMicromapsEXT'
                                                      (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                      ((Int -> Flags
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("infos" ::: Vector MicromapBuildInfoEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length (("infos" ::: Vector MicromapBuildInfoEXT) -> Int)
-> ("infos" ::: Vector MicromapBuildInfoEXT) -> Int
forall a b. (a -> b) -> a -> b
$ ("infos" ::: Vector MicromapBuildInfoEXT
infos)) :: Word32))
                                                      ("pInfos" ::: Ptr MicromapBuildInfoEXT
pPInfos))
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkBuildMicromapsEXT
  :: FunPtr (Ptr Device_T -> DeferredOperationKHR -> Word32 -> Ptr MicromapBuildInfoEXT -> IO Result) -> Ptr Device_T -> DeferredOperationKHR -> Word32 -> Ptr MicromapBuildInfoEXT -> IO Result

-- | vkBuildMicromapsEXT - Build a micromap on the host
--
-- = Description
--
-- This command fulfills the same task as 'cmdBuildMicromapsEXT' but is
-- executed by the host.
--
-- The 'buildMicromapsEXT' command provides the ability to initiate
-- multiple micromaps builds, however there is no ordering or
-- synchronization implied between any of the individual micromap builds.
--
-- Note
--
-- This means that there /cannot/ be any memory aliasing between any
-- micromap memories or scratch memories being used by any of the builds.
--
-- == Valid Usage
--
-- -   #VUID-vkBuildMicromapsEXT-pInfos-07461# For each @pInfos@[i],
--     @dstMicromap@ /must/ have been created with a value of
--     'MicromapCreateInfoEXT'::@size@ greater than or equal to the memory
--     size required by the build operation, as returned by
--     'getMicromapBuildSizesEXT' with @pBuildInfo@ = @pInfos@[i]
--
-- -   #VUID-vkBuildMicromapsEXT-mode-07462# The @mode@ member of each
--     element of @pInfos@ /must/ be a valid 'BuildMicromapModeEXT' value
--
-- -   #VUID-vkBuildMicromapsEXT-dstMicromap-07463# The @dstMicromap@
--     member of any element of @pInfos@ /must/ be a valid
--     'Vulkan.Extensions.Handles.MicromapEXT' handle
--
-- -   #VUID-vkBuildMicromapsEXT-pInfos-07464# For each element of @pInfos@
--     its @type@ member /must/ match the value of
--     'MicromapCreateInfoEXT'::@type@ when its @dstMicromap@ was created
--
-- -   #VUID-vkBuildMicromapsEXT-dstMicromap-07465# The range of memory
--     backing the @dstMicromap@ member of any element of @pInfos@ that is
--     accessed by this command /must/ not overlap the memory backing the
--     @dstMicromap@ member of any other element of @pInfos@, which is
--     accessed by this command
--
-- -   #VUID-vkBuildMicromapsEXT-dstMicromap-07466# The range of memory
--     backing the @dstMicromap@ member of any element of @pInfos@ that is
--     accessed by this command /must/ not overlap the memory backing the
--     @scratchData@ member of any element of @pInfos@ (including the same
--     element), which is accessed by this command
--
-- -   #VUID-vkBuildMicromapsEXT-scratchData-07467# The range of memory
--     backing the @scratchData@ member of any element of @pInfos@ that is
--     accessed by this command /must/ not overlap the memory backing the
--     @scratchData@ member of any other element of @pInfos@, which is
--     accessed by this command
--
-- -   #VUID-vkBuildMicromapsEXT-pInfos-07552# For each element of
--     @pInfos@, the @buffer@ used to create its @dstMicromap@ member
--     /must/ be bound to host-visible device memory
--
-- -   #VUID-vkBuildMicromapsEXT-pInfos-07553# For each element of
--     @pInfos@, all referenced addresses of @pInfos@[i].@data.hostAddress@
--     /must/ be valid host memory
--
-- -   #VUID-vkBuildMicromapsEXT-pInfos-07554# For each element of
--     @pInfos@, all referenced addresses of
--     @pInfos@[i].@triangleArray.hostAddress@ /must/ be valid host memory
--
-- -   #VUID-vkBuildMicromapsEXT-micromapHostCommands-07555# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromapHostCommands ::micromapHostCommands>
--     feature /must/ be enabled
--
-- -   #VUID-vkBuildMicromapsEXT-pInfos-07556# If @pInfos@[i].@mode@ is
--     'BUILD_MICROMAP_MODE_BUILD_EXT', all addresses between
--     @pInfos@[i].@scratchData.hostAddress@ and
--     @pInfos@[i].@scratchData.hostAddress@ + N - 1 /must/ be valid host
--     memory, where N is given by the @buildScratchSize@ member of the
--     'MicromapBuildSizesInfoEXT' structure returned from a call to
--     'getMicromapBuildSizesEXT' with an identical 'MicromapBuildInfoEXT'
--     structure and primitive count
--
-- -   #VUID-vkBuildMicromapsEXT-pInfos-07557# For each element of
--     @pInfos@, the @buffer@ used to create its @dstMicromap@ member
--     /must/ be bound to memory that was not allocated with multiple
--     instances
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkBuildMicromapsEXT-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkBuildMicromapsEXT-deferredOperation-parameter# If
--     @deferredOperation@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @deferredOperation@ /must/ be a valid
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' handle
--
-- -   #VUID-vkBuildMicromapsEXT-pInfos-parameter# @pInfos@ /must/ be a
--     valid pointer to an array of @infoCount@ valid
--     'MicromapBuildInfoEXT' structures
--
-- -   #VUID-vkBuildMicromapsEXT-infoCount-arraylength# @infoCount@ /must/
--     be greater than @0@
--
-- -   #VUID-vkBuildMicromapsEXT-deferredOperation-parent# If
--     @deferredOperation@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.OPERATION_DEFERRED_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.OPERATION_NOT_DEFERRED_KHR'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Handles.Device', 'MicromapBuildInfoEXT'
buildMicromapsEXT :: forall io
                   . (MonadIO io)
                  => -- | @device@ is the 'Vulkan.Core10.Handles.Device' for which the micromaps
                     -- are being built.
                     Device
                  -> -- | @deferredOperation@ is an optional
                     -- 'Vulkan.Extensions.Handles.DeferredOperationKHR' to
                     -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#deferred-host-operations-requesting request deferral>
                     -- for this command.
                     DeferredOperationKHR
                  -> -- | @pInfos@ is a pointer to an array of @infoCount@ 'MicromapBuildInfoEXT'
                     -- structures defining the geometry used to build each micromap.
                     ("infos" ::: Vector MicromapBuildInfoEXT)
                  -> io (Result)
buildMicromapsEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> DeferredOperationKHR
-> ("infos" ::: Vector MicromapBuildInfoEXT)
-> io Result
buildMicromapsEXT Device
device DeferredOperationKHR
deferredOperation "infos" ::: Vector MicromapBuildInfoEXT
infos = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result)
-> (ContT Result IO Result -> IO Result)
-> ContT Result IO Result
-> io Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Result IO Result -> IO Result
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Result IO Result -> io Result)
-> ContT Result IO Result -> io Result
forall a b. (a -> b) -> a -> b
$ do
  let vkBuildMicromapsEXTPtr :: FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Flags
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> IO Result)
vkBuildMicromapsEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR
      -> Flags
      -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
      -> IO Result)
pVkBuildMicromapsEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Flags
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> IO Result)
vkBuildMicromapsEXTPtr FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Flags
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR
      -> Flags
      -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Flags
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkBuildMicromapsEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkBuildMicromapsEXT' :: Ptr Device_T
-> DeferredOperationKHR
-> Flags
-> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> IO Result
vkBuildMicromapsEXT' = FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Flags
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> IO Result)
-> Ptr Device_T
-> DeferredOperationKHR
-> Flags
-> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> IO Result
mkVkBuildMicromapsEXT FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Flags
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> IO Result)
vkBuildMicromapsEXTPtr
  "pInfos" ::: Ptr MicromapBuildInfoEXT
pPInfos <- ((("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO Result)
 -> IO Result)
-> ContT Result IO ("pInfos" ::: Ptr MicromapBuildInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO Result)
  -> IO Result)
 -> ContT Result IO ("pInfos" ::: Ptr MicromapBuildInfoEXT))
-> ((("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO Result)
    -> IO Result)
-> ContT Result IO ("pInfos" ::: Ptr MicromapBuildInfoEXT)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @MicromapBuildInfoEXT ((("infos" ::: Vector MicromapBuildInfoEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length ("infos" ::: Vector MicromapBuildInfoEXT
infos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
96)
  (Int -> MicromapBuildInfoEXT -> ContT Result IO ())
-> ("infos" ::: Vector MicromapBuildInfoEXT) -> ContT Result IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i MicromapBuildInfoEXT
e -> ((() -> IO Result) -> IO Result) -> ContT Result IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO Result) -> IO Result) -> ContT Result IO ())
-> ((() -> IO Result) -> IO Result) -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> MicromapBuildInfoEXT -> IO Result -> IO Result
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pInfos" ::: Ptr MicromapBuildInfoEXT
pPInfos ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> "pInfos" ::: Ptr MicromapBuildInfoEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
96 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MicromapBuildInfoEXT) (MicromapBuildInfoEXT
e) (IO Result -> IO Result)
-> ((() -> IO Result) -> IO Result)
-> (() -> IO Result)
-> IO Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO Result) -> () -> IO Result
forall a b. (a -> b) -> a -> b
$ ())) ("infos" ::: Vector MicromapBuildInfoEXT
infos)
  Result
r <- IO Result -> ContT Result IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Result IO Result)
-> IO Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkBuildMicromapsEXT" (Ptr Device_T
-> DeferredOperationKHR
-> Flags
-> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> IO Result
vkBuildMicromapsEXT'
                                                        (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                        (DeferredOperationKHR
deferredOperation)
                                                        ((Int -> Flags
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("infos" ::: Vector MicromapBuildInfoEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length (("infos" ::: Vector MicromapBuildInfoEXT) -> Int)
-> ("infos" ::: Vector MicromapBuildInfoEXT) -> Int
forall a b. (a -> b) -> a -> b
$ ("infos" ::: Vector MicromapBuildInfoEXT
infos)) :: Word32))
                                                        ("pInfos" ::: Ptr MicromapBuildInfoEXT
pPInfos))
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Result -> ContT Result IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> ContT Result IO Result)
-> Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ (Result
r)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDestroyMicromapEXT
  :: FunPtr (Ptr Device_T -> MicromapEXT -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> MicromapEXT -> Ptr AllocationCallbacks -> IO ()

-- | vkDestroyMicromapEXT - Destroy a micromap object
--
-- == Valid Usage
--
-- -   #VUID-vkDestroyMicromapEXT-micromap-07441# All submitted commands
--     that refer to @micromap@ /must/ have completed execution
--
-- -   #VUID-vkDestroyMicromapEXT-micromap-07442# If
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @micromap@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   #VUID-vkDestroyMicromapEXT-micromap-07443# If no
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @micromap@ was created, @pAllocator@ /must/ be @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkDestroyMicromapEXT-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkDestroyMicromapEXT-micromap-parameter# If @micromap@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @micromap@ /must/ be a
--     valid 'Vulkan.Extensions.Handles.MicromapEXT' handle
--
-- -   #VUID-vkDestroyMicromapEXT-pAllocator-parameter# If @pAllocator@ is
--     not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   #VUID-vkDestroyMicromapEXT-micromap-parent# If @micromap@ is a valid
--     handle, it /must/ have been created, allocated, or retrieved from
--     @device@
--
-- == Host Synchronization
--
-- -   Host access to @micromap@ /must/ be externally synchronized
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Extensions.Handles.MicromapEXT'
destroyMicromapEXT :: forall io
                    . (MonadIO io)
                   => -- | @device@ is the logical device that destroys the micromap.
                      Device
                   -> -- | @micromap@ is the micromap to destroy.
                      MicromapEXT
                   -> -- | @pAllocator@ controls host memory allocation as described in the
                      -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                      -- chapter.
                      ("allocator" ::: Maybe AllocationCallbacks)
                   -> io ()
destroyMicromapEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> MicromapEXT
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyMicromapEXT Device
device MicromapEXT
micromap "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDestroyMicromapEXTPtr :: FunPtr
  (Ptr Device_T
   -> MicromapEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyMicromapEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> MicromapEXT
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroyMicromapEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> MicromapEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyMicromapEXTPtr FunPtr
  (Ptr Device_T
   -> MicromapEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> MicromapEXT
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> MicromapEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkDestroyMicromapEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyMicromapEXT' :: Ptr Device_T
-> MicromapEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyMicromapEXT' = FunPtr
  (Ptr Device_T
   -> MicromapEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> Ptr Device_T
-> MicromapEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyMicromapEXT FunPtr
  (Ptr Device_T
   -> MicromapEXT
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyMicromapEXTPtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDestroyMicromapEXT" (Ptr Device_T
-> MicromapEXT
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyMicromapEXT'
                                                    (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                    (MicromapEXT
micromap)
                                                    "pAllocator" ::: Ptr AllocationCallbacks
pAllocator)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdCopyMicromapEXT
  :: FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ()) -> Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ()

-- | vkCmdCopyMicromapEXT - Copy a micromap
--
-- = Description
--
-- This command copies the @pInfo->src@ micromap to the @pInfo->dst@
-- micromap in the manner specified by @pInfo->mode@.
--
-- Accesses to @pInfo->src@ and @pInfo->dst@ /must/ be
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies synchronized>
-- with the
-- 'Vulkan.Core13.Enums.PipelineStageFlags2.PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT'
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages pipeline stage>
-- and an
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types access type>
-- of 'Vulkan.Core13.Enums.AccessFlags2.ACCESS_2_MICROMAP_READ_BIT_EXT' or
-- 'Vulkan.Core13.Enums.AccessFlags2.ACCESS_2_MICROMAP_WRITE_BIT_EXT' as
-- appropriate.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdCopyMicromapEXT-buffer-07529# The @buffer@ used to create
--     @pInfo->src@ /must/ be bound to device memory
--
-- -   #VUID-vkCmdCopyMicromapEXT-buffer-07530# The @buffer@ used to create
--     @pInfo->dst@ /must/ be bound to device memory
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdCopyMicromapEXT-commandBuffer-parameter# @commandBuffer@
--     /must/ be a valid 'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdCopyMicromapEXT-pInfo-parameter# @pInfo@ /must/ be a
--     valid pointer to a valid 'CopyMicromapInfoEXT' structure
--
-- -   #VUID-vkCmdCopyMicromapEXT-commandBuffer-recording# @commandBuffer@
--     /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdCopyMicromapEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   #VUID-vkCmdCopyMicromapEXT-renderpass# This command /must/ only be
--     called outside of a render pass instance
--
-- -   #VUID-vkCmdCopyMicromapEXT-videocoding# This command /must/ only be
--     called outside of a video coding scope
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Outside                                                                                                                     | Compute                                                                                                               | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             |                                                                                                                       |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'CopyMicromapInfoEXT'
cmdCopyMicromapEXT :: forall io
                    . (MonadIO io)
                   => -- | @commandBuffer@ is the command buffer into which the command will be
                      -- recorded.
                      CommandBuffer
                   -> -- | @pInfo@ is a pointer to a 'CopyMicromapInfoEXT' structure defining the
                      -- copy operation.
                      CopyMicromapInfoEXT
                   -> io ()
cmdCopyMicromapEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> CopyMicromapInfoEXT -> io ()
cmdCopyMicromapEXT CommandBuffer
commandBuffer CopyMicromapInfoEXT
info = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdCopyMicromapEXTPtr :: FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ())
vkCmdCopyMicromapEXTPtr = DeviceCmds
-> FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ())
pVkCmdCopyMicromapEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ())
vkCmdCopyMicromapEXTPtr FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ())
-> FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ())
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkCmdCopyMicromapEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyMicromapEXT' :: Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ()
vkCmdCopyMicromapEXT' = FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ())
-> Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ()
mkVkCmdCopyMicromapEXT FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ())
vkCmdCopyMicromapEXTPtr
  Ptr CopyMicromapInfoEXT
pInfo <- ((Ptr CopyMicromapInfoEXT -> IO ()) -> IO ())
-> ContT () IO (Ptr CopyMicromapInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CopyMicromapInfoEXT -> IO ()) -> IO ())
 -> ContT () IO (Ptr CopyMicromapInfoEXT))
-> ((Ptr CopyMicromapInfoEXT -> IO ()) -> IO ())
-> ContT () IO (Ptr CopyMicromapInfoEXT)
forall a b. (a -> b) -> a -> b
$ CopyMicromapInfoEXT -> (Ptr CopyMicromapInfoEXT -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyMicromapInfoEXT
info)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdCopyMicromapEXT" (Ptr CommandBuffer_T -> Ptr CopyMicromapInfoEXT -> IO ()
vkCmdCopyMicromapEXT'
                                                    (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                    Ptr CopyMicromapInfoEXT
pInfo)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCopyMicromapEXT
  :: FunPtr (Ptr Device_T -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result) -> Ptr Device_T -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result

-- | vkCopyMicromapEXT - Copy a micromap on the host
--
-- = Description
--
-- This command fulfills the same task as 'cmdCopyMicromapEXT' but is
-- executed by the host.
--
-- == Valid Usage
--
-- -   #VUID-vkCopyMicromapEXT-deferredOperation-03677# If
--     @deferredOperation@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     it /must/ be a valid
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' object
--
-- -   #VUID-vkCopyMicromapEXT-deferredOperation-03678# Any previous
--     deferred operation that was associated with @deferredOperation@
--     /must/ be complete
--
-- -   #VUID-vkCopyMicromapEXT-buffer-07558# The @buffer@ used to create
--     @pInfo->src@ /must/ be bound to host-visible device memory
--
-- -   #VUID-vkCopyMicromapEXT-buffer-07559# The @buffer@ used to create
--     @pInfo->dst@ /must/ be bound to host-visible device memory
--
-- -   #VUID-vkCopyMicromapEXT-micromapHostCommands-07560# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromapHostCommands ::micromapHostCommands>
--     feature /must/ be enabled
--
-- -   #VUID-vkCopyMicromapEXT-buffer-07561# The @buffer@ used to create
--     @pInfo->src@ /must/ be bound to memory that was not allocated with
--     multiple instances
--
-- -   #VUID-vkCopyMicromapEXT-buffer-07562# The @buffer@ used to create
--     @pInfo->dst@ /must/ be bound to memory that was not allocated with
--     multiple instances
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCopyMicromapEXT-device-parameter# @device@ /must/ be a valid
--     'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkCopyMicromapEXT-deferredOperation-parameter# If
--     @deferredOperation@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @deferredOperation@ /must/ be a valid
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' handle
--
-- -   #VUID-vkCopyMicromapEXT-pInfo-parameter# @pInfo@ /must/ be a valid
--     pointer to a valid 'CopyMicromapInfoEXT' structure
--
-- -   #VUID-vkCopyMicromapEXT-deferredOperation-parent# If
--     @deferredOperation@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.OPERATION_DEFERRED_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.OPERATION_NOT_DEFERRED_KHR'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'CopyMicromapInfoEXT', 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Handles.Device'
copyMicromapEXT :: forall io
                 . (MonadIO io)
                => -- | @device@ is the device which owns the micromaps.
                   Device
                -> -- | @deferredOperation@ is an optional
                   -- 'Vulkan.Extensions.Handles.DeferredOperationKHR' to
                   -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#deferred-host-operations-requesting request deferral>
                   -- for this command.
                   DeferredOperationKHR
                -> -- | @pInfo@ is a pointer to a 'CopyMicromapInfoEXT' structure defining the
                   -- copy operation.
                   CopyMicromapInfoEXT
                -> io (Result)
copyMicromapEXT :: forall (io :: * -> *).
MonadIO io =>
Device -> DeferredOperationKHR -> CopyMicromapInfoEXT -> io Result
copyMicromapEXT Device
device DeferredOperationKHR
deferredOperation CopyMicromapInfoEXT
info = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result)
-> (ContT Result IO Result -> IO Result)
-> ContT Result IO Result
-> io Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Result IO Result -> IO Result
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Result IO Result -> io Result)
-> ContT Result IO Result -> io Result
forall a b. (a -> b) -> a -> b
$ do
  let vkCopyMicromapEXTPtr :: FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result)
vkCopyMicromapEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result)
pVkCopyMicromapEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result)
vkCopyMicromapEXTPtr FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result)
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkCopyMicromapEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCopyMicromapEXT' :: Ptr Device_T
-> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result
vkCopyMicromapEXT' = FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result)
-> Ptr Device_T
-> DeferredOperationKHR
-> Ptr CopyMicromapInfoEXT
-> IO Result
mkVkCopyMicromapEXT FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result)
vkCopyMicromapEXTPtr
  Ptr CopyMicromapInfoEXT
pInfo <- ((Ptr CopyMicromapInfoEXT -> IO Result) -> IO Result)
-> ContT Result IO (Ptr CopyMicromapInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CopyMicromapInfoEXT -> IO Result) -> IO Result)
 -> ContT Result IO (Ptr CopyMicromapInfoEXT))
-> ((Ptr CopyMicromapInfoEXT -> IO Result) -> IO Result)
-> ContT Result IO (Ptr CopyMicromapInfoEXT)
forall a b. (a -> b) -> a -> b
$ CopyMicromapInfoEXT
-> (Ptr CopyMicromapInfoEXT -> IO Result) -> IO Result
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyMicromapInfoEXT
info)
  Result
r <- IO Result -> ContT Result IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Result IO Result)
-> IO Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCopyMicromapEXT" (Ptr Device_T
-> DeferredOperationKHR -> Ptr CopyMicromapInfoEXT -> IO Result
vkCopyMicromapEXT'
                                                      (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                      (DeferredOperationKHR
deferredOperation)
                                                      Ptr CopyMicromapInfoEXT
pInfo)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Result -> ContT Result IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> ContT Result IO Result)
-> Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ (Result
r)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdCopyMicromapToMemoryEXT
  :: FunPtr (Ptr CommandBuffer_T -> Ptr CopyMicromapToMemoryInfoEXT -> IO ()) -> Ptr CommandBuffer_T -> Ptr CopyMicromapToMemoryInfoEXT -> IO ()

-- | vkCmdCopyMicromapToMemoryEXT - Copy a micromap to device memory
--
-- = Description
--
-- Accesses to @pInfo->src@ /must/ be
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies synchronized>
-- with the
-- 'Vulkan.Core13.Enums.PipelineStageFlags2.PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT'
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages pipeline stage>
-- and an
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types access type>
-- of 'Vulkan.Core13.Enums.AccessFlags2.ACCESS_2_MICROMAP_READ_BIT_EXT'.
-- Accesses to the buffer indicated by @pInfo->dst.deviceAddress@ /must/ be
-- synchronized with the
-- 'Vulkan.Core13.Enums.PipelineStageFlags2.PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT'
-- pipeline stage and an access type of
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_TRANSFER_WRITE_BIT'.
--
-- This command produces the same results as 'copyMicromapToMemoryEXT', but
-- writes its result to a device address, and is executed on the device
-- rather than the host. The output /may/ not necessarily be bit-for-bit
-- identical, but it can be equally used by either
-- 'cmdCopyMemoryToMicromapEXT' or 'copyMemoryToMicromapEXT'.
--
-- The defined header structure for the serialized data consists of:
--
-- -   'Vulkan.Core10.APIConstants.UUID_SIZE' bytes of data matching
--     'Vulkan.Core11.Promoted_From_VK_KHR_external_memory_capabilities.PhysicalDeviceIDProperties'::@driverUUID@
--
-- -   'Vulkan.Core10.APIConstants.UUID_SIZE' bytes of data identifying the
--     compatibility for comparison using
--     'getDeviceMicromapCompatibilityEXT' The serialized data is written
--     to the buffer (or read from the buffer) according to the host
--     endianness.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-pInfo-07536#
--     @pInfo->dst.deviceAddress@ /must/ be a valid device address for a
--     buffer bound to device memory
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-pInfo-07537#
--     @pInfo->dst.deviceAddress@ /must/ be aligned to @256@ bytes
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-pInfo-07538# If the buffer
--     pointed to by @pInfo->dst.deviceAddress@ is non-sparse then it
--     /must/ be bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-buffer-07539# The @buffer@ used
--     to create @pInfo->src@ /must/ be bound to device memory
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-pInfo-parameter# @pInfo@ /must/
--     be a valid pointer to a valid 'CopyMicromapToMemoryInfoEXT'
--     structure
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-renderpass# This command /must/
--     only be called outside of a render pass instance
--
-- -   #VUID-vkCmdCopyMicromapToMemoryEXT-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Outside                                                                                                                     | Compute                                                                                                               | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             |                                                                                                                       |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'CopyMicromapToMemoryInfoEXT'
cmdCopyMicromapToMemoryEXT :: forall io
                            . (MonadIO io)
                           => -- | @commandBuffer@ is the command buffer into which the command will be
                              -- recorded.
                              CommandBuffer
                           -> -- | @pInfo@ is an a pointer to a 'CopyMicromapToMemoryInfoEXT' structure
                              -- defining the copy operation.
                              CopyMicromapToMemoryInfoEXT
                           -> io ()
cmdCopyMicromapToMemoryEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> CopyMicromapToMemoryInfoEXT -> io ()
cmdCopyMicromapToMemoryEXT CommandBuffer
commandBuffer CopyMicromapToMemoryInfoEXT
info = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdCopyMicromapToMemoryEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
vkCmdCopyMicromapToMemoryEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
pVkCmdCopyMicromapToMemoryEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
vkCmdCopyMicromapToMemoryEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkCmdCopyMicromapToMemoryEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyMicromapToMemoryEXT' :: Ptr CommandBuffer_T
-> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ()
vkCmdCopyMicromapToMemoryEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
-> Ptr CommandBuffer_T
-> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> IO ()
mkVkCmdCopyMicromapToMemoryEXT FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
vkCmdCopyMicromapToMemoryEXTPtr
  "pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
pInfo <- ((("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ()) -> IO ())
-> ContT () IO ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
  -> IO ())
 -> ContT () IO ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT))
-> ((("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
    -> IO ())
-> ContT () IO ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
forall a b. (a -> b) -> a -> b
$ CopyMicromapToMemoryInfoEXT
-> (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyMicromapToMemoryInfoEXT
info)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdCopyMicromapToMemoryEXT" (Ptr CommandBuffer_T
-> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO ()
vkCmdCopyMicromapToMemoryEXT'
                                                            (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                            "pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
pInfo)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCopyMicromapToMemoryEXT
  :: FunPtr (Ptr Device_T -> DeferredOperationKHR -> Ptr CopyMicromapToMemoryInfoEXT -> IO Result) -> Ptr Device_T -> DeferredOperationKHR -> Ptr CopyMicromapToMemoryInfoEXT -> IO Result

-- | vkCopyMicromapToMemoryEXT - Serialize a micromap on the host
--
-- = Description
--
-- This command fulfills the same task as 'cmdCopyMicromapToMemoryEXT' but
-- is executed by the host.
--
-- This command produces the same results as 'cmdCopyMicromapToMemoryEXT',
-- but writes its result directly to a host pointer, and is executed on the
-- host rather than the device. The output /may/ not necessarily be
-- bit-for-bit identical, but it can be equally used by either
-- 'cmdCopyMemoryToMicromapEXT' or 'copyMemoryToMicromapEXT'.
--
-- == Valid Usage
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-deferredOperation-03677# If
--     @deferredOperation@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     it /must/ be a valid
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' object
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-deferredOperation-03678# Any
--     previous deferred operation that was associated with
--     @deferredOperation@ /must/ be complete
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-buffer-07568# The @buffer@ used to
--     create @pInfo->src@ /must/ be bound to host-visible device memory
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-pInfo-07569#
--     @pInfo->dst.hostAddress@ /must/ be a valid host pointer
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-pInfo-07570#
--     @pInfo->dst.hostAddress@ /must/ be aligned to 16 bytes
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-micromapHostCommands-07571# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromapHostCommands ::micromapHostCommands>
--     feature /must/ be enabled
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-buffer-07572# The @buffer@ used to
--     create @pInfo->src@ /must/ be bound to memory that was not allocated
--     with multiple instances
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-device-parameter# @device@ /must/ be
--     a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-deferredOperation-parameter# If
--     @deferredOperation@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @deferredOperation@ /must/ be a valid
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' handle
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-pInfo-parameter# @pInfo@ /must/ be a
--     valid pointer to a valid 'CopyMicromapToMemoryInfoEXT' structure
--
-- -   #VUID-vkCopyMicromapToMemoryEXT-deferredOperation-parent# If
--     @deferredOperation@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.OPERATION_DEFERRED_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.OPERATION_NOT_DEFERRED_KHR'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'CopyMicromapToMemoryInfoEXT',
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Handles.Device'
copyMicromapToMemoryEXT :: forall io
                         . (MonadIO io)
                        => -- | @device@ is the device which owns @pInfo->src@.
                           Device
                        -> -- | @deferredOperation@ is an optional
                           -- 'Vulkan.Extensions.Handles.DeferredOperationKHR' to
                           -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#deferred-host-operations-requesting request deferral>
                           -- for this command.
                           DeferredOperationKHR
                        -> -- | @pInfo@ is a pointer to a 'CopyMicromapToMemoryInfoEXT' structure
                           -- defining the copy operation.
                           CopyMicromapToMemoryInfoEXT
                        -> io (Result)
copyMicromapToMemoryEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> DeferredOperationKHR -> CopyMicromapToMemoryInfoEXT -> io Result
copyMicromapToMemoryEXT Device
device DeferredOperationKHR
deferredOperation CopyMicromapToMemoryInfoEXT
info = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result)
-> (ContT Result IO Result -> IO Result)
-> ContT Result IO Result
-> io Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Result IO Result -> IO Result
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Result IO Result -> io Result)
-> ContT Result IO Result -> io Result
forall a b. (a -> b) -> a -> b
$ do
  let vkCopyMicromapToMemoryEXTPtr :: FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
   -> IO Result)
vkCopyMicromapToMemoryEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR
      -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
      -> IO Result)
pVkCopyMicromapToMemoryEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
   -> IO Result)
vkCopyMicromapToMemoryEXTPtr FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR
      -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkCopyMicromapToMemoryEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCopyMicromapToMemoryEXT' :: Ptr Device_T
-> DeferredOperationKHR
-> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> IO Result
vkCopyMicromapToMemoryEXT' = FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
   -> IO Result)
-> Ptr Device_T
-> DeferredOperationKHR
-> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> IO Result
mkVkCopyMicromapToMemoryEXT FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
   -> IO Result)
vkCopyMicromapToMemoryEXTPtr
  "pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
pInfo <- ((("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO Result)
 -> IO Result)
-> ContT Result IO ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO Result)
  -> IO Result)
 -> ContT Result IO ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT))
-> ((("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO Result)
    -> IO Result)
-> ContT Result IO ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
forall a b. (a -> b) -> a -> b
$ CopyMicromapToMemoryInfoEXT
-> (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO Result)
-> IO Result
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyMicromapToMemoryInfoEXT
info)
  Result
r <- IO Result -> ContT Result IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Result IO Result)
-> IO Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCopyMicromapToMemoryEXT" (Ptr Device_T
-> DeferredOperationKHR
-> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> IO Result
vkCopyMicromapToMemoryEXT'
                                                              (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                              (DeferredOperationKHR
deferredOperation)
                                                              "pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
pInfo)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Result -> ContT Result IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> ContT Result IO Result)
-> Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ (Result
r)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdCopyMemoryToMicromapEXT
  :: FunPtr (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ()) -> Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ()

-- | vkCmdCopyMemoryToMicromapEXT - Copy device memory to a micromap
--
-- = Description
--
-- Accesses to @pInfo->dst@ /must/ be
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies synchronized>
-- with the
-- 'Vulkan.Core13.Enums.PipelineStageFlags2.PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT'
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages pipeline stage>
-- and an
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types access type>
-- of 'Vulkan.Core13.Enums.AccessFlags2.ACCESS_2_MICROMAP_READ_BIT_EXT'.
-- Accesses to the buffer indicated by @pInfo->src.deviceAddress@ /must/ be
-- synchronized with the
-- 'Vulkan.Core13.Enums.PipelineStageFlags2.PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT'
-- pipeline stage and an access type of
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_TRANSFER_READ_BIT'.
--
-- This command can accept micromaps produced by either
-- 'cmdCopyMicromapToMemoryEXT' or 'copyMicromapToMemoryEXT'.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-pInfo-07543#
--     @pInfo->src.deviceAddress@ /must/ be a valid device address for a
--     buffer bound to device memory
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-pInfo-07544#
--     @pInfo->src.deviceAddress@ /must/ be aligned to @256@ bytes
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-pInfo-07545# If the buffer
--     pointed to by @pInfo->src.deviceAddress@ is non-sparse then it
--     /must/ be bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-buffer-07546# The @buffer@ used
--     to create @pInfo->dst@ /must/ be bound to device memory
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-pInfo-parameter# @pInfo@ /must/
--     be a valid pointer to a valid 'CopyMemoryToMicromapInfoEXT'
--     structure
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-renderpass# This command /must/
--     only be called outside of a render pass instance
--
-- -   #VUID-vkCmdCopyMemoryToMicromapEXT-videocoding# This command /must/
--     only be called outside of a video coding scope
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Outside                                                                                                                     | Compute                                                                                                               | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             |                                                                                                                       |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.Handles.CommandBuffer', 'CopyMemoryToMicromapInfoEXT'
cmdCopyMemoryToMicromapEXT :: forall io
                            . (MonadIO io)
                           => -- | @commandBuffer@ is the command buffer into which the command will be
                              -- recorded.
                              CommandBuffer
                           -> -- | @pInfo@ is a pointer to a 'CopyMicromapToMemoryInfoEXT' structure
                              -- defining the copy operation.
                              CopyMemoryToMicromapInfoEXT
                           -> io ()
cmdCopyMemoryToMicromapEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer -> CopyMemoryToMicromapInfoEXT -> io ()
cmdCopyMemoryToMicromapEXT CommandBuffer
commandBuffer CopyMemoryToMicromapInfoEXT
info = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdCopyMemoryToMicromapEXTPtr :: FunPtr
  (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ())
vkCmdCopyMemoryToMicromapEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ())
pVkCmdCopyMemoryToMicromapEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ())
vkCmdCopyMemoryToMicromapEXTPtr FunPtr
  (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ())
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkCmdCopyMemoryToMicromapEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyMemoryToMicromapEXT' :: Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ()
vkCmdCopyMemoryToMicromapEXT' = FunPtr
  (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ())
-> Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ()
mkVkCmdCopyMemoryToMicromapEXT FunPtr
  (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ())
vkCmdCopyMemoryToMicromapEXTPtr
  Ptr CopyMemoryToMicromapInfoEXT
pInfo <- ((Ptr CopyMemoryToMicromapInfoEXT -> IO ()) -> IO ())
-> ContT () IO (Ptr CopyMemoryToMicromapInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CopyMemoryToMicromapInfoEXT -> IO ()) -> IO ())
 -> ContT () IO (Ptr CopyMemoryToMicromapInfoEXT))
-> ((Ptr CopyMemoryToMicromapInfoEXT -> IO ()) -> IO ())
-> ContT () IO (Ptr CopyMemoryToMicromapInfoEXT)
forall a b. (a -> b) -> a -> b
$ CopyMemoryToMicromapInfoEXT
-> (Ptr CopyMemoryToMicromapInfoEXT -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyMemoryToMicromapInfoEXT
info)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdCopyMemoryToMicromapEXT" (Ptr CommandBuffer_T -> Ptr CopyMemoryToMicromapInfoEXT -> IO ()
vkCmdCopyMemoryToMicromapEXT'
                                                            (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                            Ptr CopyMemoryToMicromapInfoEXT
pInfo)
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCopyMemoryToMicromapEXT
  :: FunPtr (Ptr Device_T -> DeferredOperationKHR -> Ptr CopyMemoryToMicromapInfoEXT -> IO Result) -> Ptr Device_T -> DeferredOperationKHR -> Ptr CopyMemoryToMicromapInfoEXT -> IO Result

-- | vkCopyMemoryToMicromapEXT - Deserialize a micromap on the host
--
-- = Description
--
-- This command fulfills the same task as 'cmdCopyMemoryToMicromapEXT' but
-- is executed by the host.
--
-- This command can accept micromaps produced by either
-- 'cmdCopyMicromapToMemoryEXT' or 'copyMicromapToMemoryEXT'.
--
-- == Valid Usage
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-deferredOperation-03677# If
--     @deferredOperation@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     it /must/ be a valid
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' object
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-deferredOperation-03678# Any
--     previous deferred operation that was associated with
--     @deferredOperation@ /must/ be complete
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-pInfo-07563#
--     @pInfo->src.hostAddress@ /must/ be a valid host pointer
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-pInfo-07564#
--     @pInfo->src.hostAddress@ /must/ be aligned to 16 bytes
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-buffer-07565# The @buffer@ used to
--     create @pInfo->dst@ /must/ be bound to host-visible device memory
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-micromapHostCommands-07566# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromapHostCommands ::micromapHostCommands>
--     feature /must/ be enabled
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-buffer-07567# The @buffer@ used to
--     create @pInfo->dst@ /must/ be bound to memory that was not allocated
--     with multiple instances
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-device-parameter# @device@ /must/ be
--     a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-deferredOperation-parameter# If
--     @deferredOperation@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @deferredOperation@ /must/ be a valid
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' handle
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-pInfo-parameter# @pInfo@ /must/ be a
--     valid pointer to a valid 'CopyMemoryToMicromapInfoEXT' structure
--
-- -   #VUID-vkCopyMemoryToMicromapEXT-deferredOperation-parent# If
--     @deferredOperation@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.OPERATION_DEFERRED_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.OPERATION_NOT_DEFERRED_KHR'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'CopyMemoryToMicromapInfoEXT',
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Handles.Device'
copyMemoryToMicromapEXT :: forall io
                         . (MonadIO io)
                        => -- | @device@ is the device which owns @pInfo->dst@.
                           Device
                        -> -- | @deferredOperation@ is an optional
                           -- 'Vulkan.Extensions.Handles.DeferredOperationKHR' to
                           -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#deferred-host-operations-requesting request deferral>
                           -- for this command.
                           DeferredOperationKHR
                        -> -- | @pInfo@ is a pointer to a 'CopyMemoryToMicromapInfoEXT' structure
                           -- defining the copy operation.
                           CopyMemoryToMicromapInfoEXT
                        -> io (Result)
copyMemoryToMicromapEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> DeferredOperationKHR -> CopyMemoryToMicromapInfoEXT -> io Result
copyMemoryToMicromapEXT Device
device DeferredOperationKHR
deferredOperation CopyMemoryToMicromapInfoEXT
info = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result)
-> (ContT Result IO Result -> IO Result)
-> ContT Result IO Result
-> io Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Result IO Result -> IO Result
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Result IO Result -> io Result)
-> ContT Result IO Result -> io Result
forall a b. (a -> b) -> a -> b
$ do
  let vkCopyMemoryToMicromapEXTPtr :: FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Ptr CopyMemoryToMicromapInfoEXT
   -> IO Result)
vkCopyMemoryToMicromapEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR
      -> Ptr CopyMemoryToMicromapInfoEXT
      -> IO Result)
pVkCopyMemoryToMicromapEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Ptr CopyMemoryToMicromapInfoEXT
   -> IO Result)
vkCopyMemoryToMicromapEXTPtr FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Ptr CopyMemoryToMicromapInfoEXT
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR
      -> Ptr CopyMemoryToMicromapInfoEXT
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Ptr CopyMemoryToMicromapInfoEXT
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkCopyMemoryToMicromapEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCopyMemoryToMicromapEXT' :: Ptr Device_T
-> DeferredOperationKHR
-> Ptr CopyMemoryToMicromapInfoEXT
-> IO Result
vkCopyMemoryToMicromapEXT' = FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Ptr CopyMemoryToMicromapInfoEXT
   -> IO Result)
-> Ptr Device_T
-> DeferredOperationKHR
-> Ptr CopyMemoryToMicromapInfoEXT
-> IO Result
mkVkCopyMemoryToMicromapEXT FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> Ptr CopyMemoryToMicromapInfoEXT
   -> IO Result)
vkCopyMemoryToMicromapEXTPtr
  Ptr CopyMemoryToMicromapInfoEXT
pInfo <- ((Ptr CopyMemoryToMicromapInfoEXT -> IO Result) -> IO Result)
-> ContT Result IO (Ptr CopyMemoryToMicromapInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CopyMemoryToMicromapInfoEXT -> IO Result) -> IO Result)
 -> ContT Result IO (Ptr CopyMemoryToMicromapInfoEXT))
-> ((Ptr CopyMemoryToMicromapInfoEXT -> IO Result) -> IO Result)
-> ContT Result IO (Ptr CopyMemoryToMicromapInfoEXT)
forall a b. (a -> b) -> a -> b
$ CopyMemoryToMicromapInfoEXT
-> (Ptr CopyMemoryToMicromapInfoEXT -> IO Result) -> IO Result
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyMemoryToMicromapInfoEXT
info)
  Result
r <- IO Result -> ContT Result IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Result IO Result)
-> IO Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCopyMemoryToMicromapEXT" (Ptr Device_T
-> DeferredOperationKHR
-> Ptr CopyMemoryToMicromapInfoEXT
-> IO Result
vkCopyMemoryToMicromapEXT'
                                                              (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                              (DeferredOperationKHR
deferredOperation)
                                                              Ptr CopyMemoryToMicromapInfoEXT
pInfo)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Result -> ContT Result IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> ContT Result IO Result)
-> Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ (Result
r)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdWriteMicromapsPropertiesEXT
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr MicromapEXT -> QueryType -> QueryPool -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr MicromapEXT -> QueryType -> QueryPool -> Word32 -> IO ()

-- | vkCmdWriteMicromapsPropertiesEXT - Write micromap result parameters to
-- query results.
--
-- = Description
--
-- Accesses to any of the micromaps listed in @pMicromaps@ /must/ be
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-dependencies synchronized>
-- with the
-- 'Vulkan.Core13.Enums.PipelineStageFlags2.PIPELINE_STAGE_2_MICROMAP_BUILD_BIT_EXT'
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-pipeline-stages pipeline stage>
-- and an
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-access-types access type>
-- of 'Vulkan.Core13.Enums.AccessFlags2.ACCESS_2_MICROMAP_READ_BIT_EXT'.
--
-- -   If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_SERIALIZATION_SIZE_EXT',
--     then the value written out is the number of bytes required by a
--     serialized micromap.
--
-- -   If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_COMPACTED_SIZE_EXT',
--     then the value written out is the number of bytes required by a
--     compacted micromap.
--
-- == Valid Usage
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-queryPool-07525# @queryPool@
--     /must/ have been created with a @queryType@ matching @queryType@
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-queryPool-07526# The queries
--     identified by @queryPool@ and @firstQuery@ /must/ be /unavailable/
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-buffer-07527# The @buffer@
--     used to create each micromap in @pMicrmaps@ /must/ be bound to
--     device memory
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-query-07528# The sum of
--     @query@ plus @micromapCount@ /must/ be less than or equal to the
--     number of queries in @queryPool@
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-pMicromaps-07501# All
--     micromaps in @pMicromaps@ /must/ have been constructed prior to the
--     execution of this command
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-pMicromaps-07502# All
--     micromaps in @pMicromaps@ /must/ have been constructed with
--     'BUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT' if @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_COMPACTED_SIZE_EXT'
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-queryType-07503# @queryType@
--     /must/ be
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_COMPACTED_SIZE_EXT'
--     or
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_SERIALIZATION_SIZE_EXT'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-commandBuffer-parameter#
--     @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-pMicromaps-parameter#
--     @pMicromaps@ /must/ be a valid pointer to an array of
--     @micromapCount@ valid 'Vulkan.Extensions.Handles.MicromapEXT'
--     handles
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-queryType-parameter#
--     @queryType@ /must/ be a valid
--     'Vulkan.Core10.Enums.QueryType.QueryType' value
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-queryPool-parameter#
--     @queryPool@ /must/ be a valid 'Vulkan.Core10.Handles.QueryPool'
--     handle
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-commandBuffer-recording#
--     @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-commandBuffer-cmdpool# The
--     'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-renderpass# This command
--     /must/ only be called outside of a render pass instance
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-videocoding# This command
--     /must/ only be called outside of a video coding scope
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-micromapCount-arraylength#
--     @micromapCount@ /must/ be greater than @0@
--
-- -   #VUID-vkCmdWriteMicromapsPropertiesEXT-commonparent# Each of
--     @commandBuffer@, @queryPool@, and the elements of @pMicromaps@
--     /must/ have been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- == Host Synchronization
--
-- -   Host access to @commandBuffer@ /must/ be externally synchronized
--
-- -   Host access to the 'Vulkan.Core10.Handles.CommandPool' that
--     @commandBuffer@ was allocated from /must/ be externally synchronized
--
-- == Command Properties
--
-- \'
--
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
-- | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkCommandBufferLevel Command Buffer Levels> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginRenderPass Render Pass Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#vkCmdBeginVideoCodingKHR Video Coding Scope> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-queueoperation-command-types Command Type> |
-- +============================================================================================================================+========================================================================================================================+=============================================================================================================================+=======================================================================================================================+========================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Outside                                                                                                                     | Compute                                                                                                               | Action                                                                                                                                 |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                             |                                                                                                                       |                                                                                                                                        |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+----------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Extensions.Handles.MicromapEXT',
-- 'Vulkan.Core10.Handles.QueryPool',
-- 'Vulkan.Core10.Enums.QueryType.QueryType'
cmdWriteMicromapsPropertiesEXT :: forall io
                                . (MonadIO io)
                               => -- | @commandBuffer@ is the command buffer into which the command will be
                                  -- recorded.
                                  CommandBuffer
                               -> -- | @pMicromaps@ is a pointer to an array of existing previously built
                                  -- micromaps.
                                  ("micromaps" ::: Vector MicromapEXT)
                               -> -- | @queryType@ is a 'Vulkan.Core10.Enums.QueryType.QueryType' value
                                  -- specifying the type of queries managed by the pool.
                                  QueryType
                               -> -- | @queryPool@ is the query pool that will manage the results of the query.
                                  QueryPool
                               -> -- | @firstQuery@ is the first query index within the query pool that will
                                  -- contain the @micromapCount@ number of results.
                                  ("firstQuery" ::: Word32)
                               -> io ()
cmdWriteMicromapsPropertiesEXT :: forall (io :: * -> *).
MonadIO io =>
CommandBuffer
-> ("micromaps" ::: Vector MicromapEXT)
-> QueryType
-> QueryPool
-> Flags
-> io ()
cmdWriteMicromapsPropertiesEXT CommandBuffer
commandBuffer
                                 "micromaps" ::: Vector MicromapEXT
micromaps
                                 QueryType
queryType
                                 QueryPool
queryPool
                                 Flags
firstQuery = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkCmdWriteMicromapsPropertiesEXTPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> QueryPool
   -> Flags
   -> IO ())
vkCmdWriteMicromapsPropertiesEXTPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> Flags
      -> ("pMicromap" ::: Ptr MicromapEXT)
      -> QueryType
      -> QueryPool
      -> Flags
      -> IO ())
pVkCmdWriteMicromapsPropertiesEXT (case CommandBuffer
commandBuffer of CommandBuffer{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:CommandBuffer :: CommandBuffer -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> QueryPool
   -> Flags
   -> IO ())
vkCmdWriteMicromapsPropertiesEXTPtr FunPtr
  (Ptr CommandBuffer_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> QueryPool
   -> Flags
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> Flags
      -> ("pMicromap" ::: Ptr MicromapEXT)
      -> QueryType
      -> QueryPool
      -> Flags
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> QueryPool
   -> Flags
   -> IO ())
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkCmdWriteMicromapsPropertiesEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdWriteMicromapsPropertiesEXT' :: Ptr CommandBuffer_T
-> Flags
-> ("pMicromap" ::: Ptr MicromapEXT)
-> QueryType
-> QueryPool
-> Flags
-> IO ()
vkCmdWriteMicromapsPropertiesEXT' = FunPtr
  (Ptr CommandBuffer_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> QueryPool
   -> Flags
   -> IO ())
-> Ptr CommandBuffer_T
-> Flags
-> ("pMicromap" ::: Ptr MicromapEXT)
-> QueryType
-> QueryPool
-> Flags
-> IO ()
mkVkCmdWriteMicromapsPropertiesEXT FunPtr
  (Ptr CommandBuffer_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> QueryPool
   -> Flags
   -> IO ())
vkCmdWriteMicromapsPropertiesEXTPtr
  "pMicromap" ::: Ptr MicromapEXT
pPMicromaps <- ((("pMicromap" ::: Ptr MicromapEXT) -> IO ()) -> IO ())
-> ContT () IO ("pMicromap" ::: Ptr MicromapEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMicromap" ::: Ptr MicromapEXT) -> IO ()) -> IO ())
 -> ContT () IO ("pMicromap" ::: Ptr MicromapEXT))
-> ((("pMicromap" ::: Ptr MicromapEXT) -> IO ()) -> IO ())
-> ContT () IO ("pMicromap" ::: Ptr MicromapEXT)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @MicromapEXT ((("micromaps" ::: Vector MicromapEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length ("micromaps" ::: Vector MicromapEXT
micromaps)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> MicromapEXT -> IO ())
-> ("micromaps" ::: Vector MicromapEXT) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i MicromapEXT
e -> ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pMicromap" ::: Ptr MicromapEXT
pPMicromaps ("pMicromap" ::: Ptr MicromapEXT)
-> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MicromapEXT) (MicromapEXT
e)) ("micromaps" ::: Vector MicromapEXT
micromaps)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCmdWriteMicromapsPropertiesEXT" (Ptr CommandBuffer_T
-> Flags
-> ("pMicromap" ::: Ptr MicromapEXT)
-> QueryType
-> QueryPool
-> Flags
-> IO ()
vkCmdWriteMicromapsPropertiesEXT'
                                                                (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer))
                                                                ((Int -> Flags
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("micromaps" ::: Vector MicromapEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length (("micromaps" ::: Vector MicromapEXT) -> Int)
-> ("micromaps" ::: Vector MicromapEXT) -> Int
forall a b. (a -> b) -> a -> b
$ ("micromaps" ::: Vector MicromapEXT
micromaps)) :: Word32))
                                                                ("pMicromap" ::: Ptr MicromapEXT
pPMicromaps)
                                                                (QueryType
queryType)
                                                                (QueryPool
queryPool)
                                                                (Flags
firstQuery))
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkWriteMicromapsPropertiesEXT
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr MicromapEXT -> QueryType -> CSize -> Ptr () -> CSize -> IO Result) -> Ptr Device_T -> Word32 -> Ptr MicromapEXT -> QueryType -> CSize -> Ptr () -> CSize -> IO Result

-- | vkWriteMicromapsPropertiesEXT - Query micromap meta-data on the host
--
-- = Description
--
-- This command fulfills the same task as 'cmdWriteMicromapsPropertiesEXT'
-- but is executed by the host.
--
-- == Valid Usage
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-pMicromaps-07501# All micromaps
--     in @pMicromaps@ /must/ have been constructed prior to the execution
--     of this command
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-pMicromaps-07502# All micromaps
--     in @pMicromaps@ /must/ have been constructed with
--     'BUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT' if @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_COMPACTED_SIZE_EXT'
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-queryType-07503# @queryType@
--     /must/ be
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_COMPACTED_SIZE_EXT'
--     or
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_SERIALIZATION_SIZE_EXT'
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-queryType-07573# If @queryType@
--     is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_SERIALIZATION_SIZE_EXT',
--     then @stride@ /must/ be a multiple of the size of
--     'Vulkan.Core10.FundamentalTypes.DeviceSize'
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-queryType-07574# If @queryType@
--     is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_SERIALIZATION_SIZE_EXT',
--     then @pData@ /must/ point to a
--     'Vulkan.Core10.FundamentalTypes.DeviceSize'
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-queryType-07575# If @queryType@
--     is
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-dataSize-07576# @dataSize@
--     /must/ be greater than or equal to @micromapCount@*@stride@
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-buffer-07577# The @buffer@ used
--     to create each micromap in @pMicromaps@ /must/ be bound to
--     host-visible device memory
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-micromapHostCommands-07578# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromapHostCommands ::micromapHostCommands>
--     feature /must/ be enabled
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-buffer-07579# The @buffer@ used
--     to create each micromap in @pMicromaps@ /must/ be bound to memory
--     that was not allocated with multiple instances
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-device-parameter# @device@
--     /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-pMicromaps-parameter#
--     @pMicromaps@ /must/ be a valid pointer to an array of
--     @micromapCount@ valid 'Vulkan.Extensions.Handles.MicromapEXT'
--     handles
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-queryType-parameter# @queryType@
--     /must/ be a valid 'Vulkan.Core10.Enums.QueryType.QueryType' value
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-pData-parameter# @pData@ /must/
--     be a valid pointer to an array of @dataSize@ bytes
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-micromapCount-arraylength#
--     @micromapCount@ /must/ be greater than @0@
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-dataSize-arraylength# @dataSize@
--     /must/ be greater than @0@
--
-- -   #VUID-vkWriteMicromapsPropertiesEXT-pMicromaps-parent# Each element
--     of @pMicromaps@ /must/ have been created, allocated, or retrieved
--     from @device@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Extensions.Handles.MicromapEXT',
-- 'Vulkan.Core10.Enums.QueryType.QueryType'
writeMicromapsPropertiesEXT :: forall io
                             . (MonadIO io)
                            => -- | @device@ is the device which owns the micromaps in @pMicromaps@.
                               Device
                            -> -- | @pMicromaps@ is a pointer to an array of existing previously built
                               -- micromaps.
                               ("micromaps" ::: Vector MicromapEXT)
                            -> -- | @queryType@ is a 'Vulkan.Core10.Enums.QueryType.QueryType' value
                               -- specifying the property to be queried.
                               QueryType
                            -> -- | @dataSize@ is the size in bytes of the buffer pointed to by @pData@.
                               ("dataSize" ::: Word64)
                            -> -- | @pData@ is a pointer to a user-allocated buffer where the results will
                               -- be written.
                               ("data" ::: Ptr ())
                            -> -- | @stride@ is the stride in bytes between results for individual queries
                               -- within @pData@.
                               ("stride" ::: Word64)
                            -> io ()
writeMicromapsPropertiesEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> ("micromaps" ::: Vector MicromapEXT)
-> QueryType
-> ("dataSize" ::: Word64)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: Word64)
-> io ()
writeMicromapsPropertiesEXT Device
device
                              "micromaps" ::: Vector MicromapEXT
micromaps
                              QueryType
queryType
                              "dataSize" ::: Word64
dataSize
                              "data" ::: Ptr ()
data'
                              "dataSize" ::: Word64
stride = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkWriteMicromapsPropertiesEXTPtr :: FunPtr
  (Ptr Device_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
vkWriteMicromapsPropertiesEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Flags
      -> ("pMicromap" ::: Ptr MicromapEXT)
      -> QueryType
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> ("dataSize" ::: CSize)
      -> IO Result)
pVkWriteMicromapsPropertiesEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
vkWriteMicromapsPropertiesEXTPtr FunPtr
  (Ptr Device_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> Flags
      -> ("pMicromap" ::: Ptr MicromapEXT)
      -> QueryType
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> ("dataSize" ::: CSize)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkWriteMicromapsPropertiesEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkWriteMicromapsPropertiesEXT' :: Ptr Device_T
-> Flags
-> ("pMicromap" ::: Ptr MicromapEXT)
-> QueryType
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: CSize)
-> IO Result
vkWriteMicromapsPropertiesEXT' = FunPtr
  (Ptr Device_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
-> Ptr Device_T
-> Flags
-> ("pMicromap" ::: Ptr MicromapEXT)
-> QueryType
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: CSize)
-> IO Result
mkVkWriteMicromapsPropertiesEXT FunPtr
  (Ptr Device_T
   -> Flags
   -> ("pMicromap" ::: Ptr MicromapEXT)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
vkWriteMicromapsPropertiesEXTPtr
  "pMicromap" ::: Ptr MicromapEXT
pPMicromaps <- ((("pMicromap" ::: Ptr MicromapEXT) -> IO ()) -> IO ())
-> ContT () IO ("pMicromap" ::: Ptr MicromapEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMicromap" ::: Ptr MicromapEXT) -> IO ()) -> IO ())
 -> ContT () IO ("pMicromap" ::: Ptr MicromapEXT))
-> ((("pMicromap" ::: Ptr MicromapEXT) -> IO ()) -> IO ())
-> ContT () IO ("pMicromap" ::: Ptr MicromapEXT)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @MicromapEXT ((("micromaps" ::: Vector MicromapEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length ("micromaps" ::: Vector MicromapEXT
micromaps)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> MicromapEXT -> IO ())
-> ("micromaps" ::: Vector MicromapEXT) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i MicromapEXT
e -> ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pMicromap" ::: Ptr MicromapEXT
pPMicromaps ("pMicromap" ::: Ptr MicromapEXT)
-> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MicromapEXT) (MicromapEXT
e)) ("micromaps" ::: Vector MicromapEXT
micromaps)
  Result
r <- IO Result -> ContT () IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT () IO Result)
-> IO Result -> ContT () IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkWriteMicromapsPropertiesEXT" (Ptr Device_T
-> Flags
-> ("pMicromap" ::: Ptr MicromapEXT)
-> QueryType
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: CSize)
-> IO Result
vkWriteMicromapsPropertiesEXT'
                                                                  (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                  ((Int -> Flags
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("micromaps" ::: Vector MicromapEXT) -> Int
forall a. Vector a -> Int
Data.Vector.length (("micromaps" ::: Vector MicromapEXT) -> Int)
-> ("micromaps" ::: Vector MicromapEXT) -> Int
forall a b. (a -> b) -> a -> b
$ ("micromaps" ::: Vector MicromapEXT
micromaps)) :: Word32))
                                                                  ("pMicromap" ::: Ptr MicromapEXT
pPMicromaps)
                                                                  (QueryType
queryType)
                                                                  (("dataSize" ::: Word64) -> "dataSize" ::: CSize
CSize ("dataSize" ::: Word64
dataSize))
                                                                  ("data" ::: Ptr ()
data')
                                                                  (("dataSize" ::: Word64) -> "dataSize" ::: CSize
CSize ("dataSize" ::: Word64
stride)))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetDeviceMicromapCompatibilityEXT
  :: FunPtr (Ptr Device_T -> Ptr MicromapVersionInfoEXT -> Ptr AccelerationStructureCompatibilityKHR -> IO ()) -> Ptr Device_T -> Ptr MicromapVersionInfoEXT -> Ptr AccelerationStructureCompatibilityKHR -> IO ()

-- | vkGetDeviceMicromapCompatibilityEXT - Check if a serialized micromap is
-- compatible with the current device
--
-- == Valid Usage
--
-- -   #VUID-vkGetDeviceMicromapCompatibilityEXT-micromap-07551# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromap micromap>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkGetDeviceMicromapCompatibilityEXT-device-parameter# @device@
--     /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkGetDeviceMicromapCompatibilityEXT-pVersionInfo-parameter#
--     @pVersionInfo@ /must/ be a valid pointer to a valid
--     'MicromapVersionInfoEXT' structure
--
-- -   #VUID-vkGetDeviceMicromapCompatibilityEXT-pCompatibility-parameter#
--     @pCompatibility@ /must/ be a valid pointer to a
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.AccelerationStructureCompatibilityKHR'
--     value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.AccelerationStructureCompatibilityKHR',
-- 'Vulkan.Core10.Handles.Device', 'MicromapVersionInfoEXT'
getDeviceMicromapCompatibilityEXT :: forall io
                                   . (MonadIO io)
                                  => -- | @device@ is the device to check the version against.
                                     Device
                                  -> -- | @pVersionInfo@ is a pointer to a 'MicromapVersionInfoEXT' structure
                                     -- specifying version information to check against the device.
                                     MicromapVersionInfoEXT
                                  -> io (AccelerationStructureCompatibilityKHR)
getDeviceMicromapCompatibilityEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> MicromapVersionInfoEXT
-> io AccelerationStructureCompatibilityKHR
getDeviceMicromapCompatibilityEXT Device
device MicromapVersionInfoEXT
versionInfo = IO AccelerationStructureCompatibilityKHR
-> io AccelerationStructureCompatibilityKHR
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AccelerationStructureCompatibilityKHR
 -> io AccelerationStructureCompatibilityKHR)
-> (ContT
      AccelerationStructureCompatibilityKHR
      IO
      AccelerationStructureCompatibilityKHR
    -> IO AccelerationStructureCompatibilityKHR)
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     AccelerationStructureCompatibilityKHR
-> io AccelerationStructureCompatibilityKHR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  AccelerationStructureCompatibilityKHR
  IO
  AccelerationStructureCompatibilityKHR
-> IO AccelerationStructureCompatibilityKHR
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   AccelerationStructureCompatibilityKHR
   IO
   AccelerationStructureCompatibilityKHR
 -> io AccelerationStructureCompatibilityKHR)
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     AccelerationStructureCompatibilityKHR
-> io AccelerationStructureCompatibilityKHR
forall a b. (a -> b) -> a -> b
$ do
  let vkGetDeviceMicromapCompatibilityEXTPtr :: FunPtr
  (Ptr Device_T
   -> Ptr MicromapVersionInfoEXT
   -> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
   -> IO ())
vkGetDeviceMicromapCompatibilityEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Ptr MicromapVersionInfoEXT
      -> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
      -> IO ())
pVkGetDeviceMicromapCompatibilityEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT AccelerationStructureCompatibilityKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT AccelerationStructureCompatibilityKHR IO ())
-> IO () -> ContT AccelerationStructureCompatibilityKHR IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Ptr MicromapVersionInfoEXT
   -> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
   -> IO ())
vkGetDeviceMicromapCompatibilityEXTPtr FunPtr
  (Ptr Device_T
   -> Ptr MicromapVersionInfoEXT
   -> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> Ptr MicromapVersionInfoEXT
      -> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Ptr MicromapVersionInfoEXT
   -> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkGetDeviceMicromapCompatibilityEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeviceMicromapCompatibilityEXT' :: Ptr Device_T
-> Ptr MicromapVersionInfoEXT
-> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
-> IO ()
vkGetDeviceMicromapCompatibilityEXT' = FunPtr
  (Ptr Device_T
   -> Ptr MicromapVersionInfoEXT
   -> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
   -> IO ())
-> Ptr Device_T
-> Ptr MicromapVersionInfoEXT
-> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
-> IO ()
mkVkGetDeviceMicromapCompatibilityEXT FunPtr
  (Ptr Device_T
   -> Ptr MicromapVersionInfoEXT
   -> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
   -> IO ())
vkGetDeviceMicromapCompatibilityEXTPtr
  Ptr MicromapVersionInfoEXT
pVersionInfo <- ((Ptr MicromapVersionInfoEXT
  -> IO AccelerationStructureCompatibilityKHR)
 -> IO AccelerationStructureCompatibilityKHR)
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     (Ptr MicromapVersionInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr MicromapVersionInfoEXT
   -> IO AccelerationStructureCompatibilityKHR)
  -> IO AccelerationStructureCompatibilityKHR)
 -> ContT
      AccelerationStructureCompatibilityKHR
      IO
      (Ptr MicromapVersionInfoEXT))
-> ((Ptr MicromapVersionInfoEXT
     -> IO AccelerationStructureCompatibilityKHR)
    -> IO AccelerationStructureCompatibilityKHR)
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     (Ptr MicromapVersionInfoEXT)
forall a b. (a -> b) -> a -> b
$ MicromapVersionInfoEXT
-> (Ptr MicromapVersionInfoEXT
    -> IO AccelerationStructureCompatibilityKHR)
-> IO AccelerationStructureCompatibilityKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MicromapVersionInfoEXT
versionInfo)
  "pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR
pPCompatibility <- ((("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
  -> IO AccelerationStructureCompatibilityKHR)
 -> IO AccelerationStructureCompatibilityKHR)
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
   -> IO AccelerationStructureCompatibilityKHR)
  -> IO AccelerationStructureCompatibilityKHR)
 -> ContT
      AccelerationStructureCompatibilityKHR
      IO
      ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR))
-> ((("pCompatibility"
      ::: Ptr AccelerationStructureCompatibilityKHR)
     -> IO AccelerationStructureCompatibilityKHR)
    -> IO AccelerationStructureCompatibilityKHR)
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
forall a b. (a -> b) -> a -> b
$ IO ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
-> (("pCompatibility"
     ::: Ptr AccelerationStructureCompatibilityKHR)
    -> IO ())
-> (("pCompatibility"
     ::: Ptr AccelerationStructureCompatibilityKHR)
    -> IO AccelerationStructureCompatibilityKHR)
-> IO AccelerationStructureCompatibilityKHR
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @AccelerationStructureCompatibilityKHR Int
4) ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
-> IO ()
forall a. Ptr a -> IO ()
free
  IO () -> ContT AccelerationStructureCompatibilityKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT AccelerationStructureCompatibilityKHR IO ())
-> IO () -> ContT AccelerationStructureCompatibilityKHR IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetDeviceMicromapCompatibilityEXT" (Ptr Device_T
-> Ptr MicromapVersionInfoEXT
-> ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR)
-> IO ()
vkGetDeviceMicromapCompatibilityEXT'
                                                                   (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                                   Ptr MicromapVersionInfoEXT
pVersionInfo
                                                                   ("pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR
pPCompatibility))
  AccelerationStructureCompatibilityKHR
pCompatibility <- IO AccelerationStructureCompatibilityKHR
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     AccelerationStructureCompatibilityKHR
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO AccelerationStructureCompatibilityKHR
 -> ContT
      AccelerationStructureCompatibilityKHR
      IO
      AccelerationStructureCompatibilityKHR)
-> IO AccelerationStructureCompatibilityKHR
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     AccelerationStructureCompatibilityKHR
forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureCompatibilityKHR "pCompatibility" ::: Ptr AccelerationStructureCompatibilityKHR
pPCompatibility
  AccelerationStructureCompatibilityKHR
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     AccelerationStructureCompatibilityKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AccelerationStructureCompatibilityKHR
 -> ContT
      AccelerationStructureCompatibilityKHR
      IO
      AccelerationStructureCompatibilityKHR)
-> AccelerationStructureCompatibilityKHR
-> ContT
     AccelerationStructureCompatibilityKHR
     IO
     AccelerationStructureCompatibilityKHR
forall a b. (a -> b) -> a -> b
$ (AccelerationStructureCompatibilityKHR
pCompatibility)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetMicromapBuildSizesEXT
  :: FunPtr (Ptr Device_T -> AccelerationStructureBuildTypeKHR -> Ptr MicromapBuildInfoEXT -> Ptr MicromapBuildSizesInfoEXT -> IO ()) -> Ptr Device_T -> AccelerationStructureBuildTypeKHR -> Ptr MicromapBuildInfoEXT -> Ptr MicromapBuildSizesInfoEXT -> IO ()

-- | vkGetMicromapBuildSizesEXT - Retrieve the required size for a micromap
--
-- = Description
--
-- The @dstMicromap@ and @mode@ members of @pBuildInfo@ are ignored. Any
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.DeviceOrHostAddressKHR'
-- members of @pBuildInfo@ are ignored by this command.
--
-- A micromap created with the @micromapSize@ returned by this command
-- supports any build with a 'MicromapBuildInfoEXT' structure subject to
-- the following properties:
--
-- -   The build command is a host build command, and @buildType@ is
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR'
--     or
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR'
--
-- -   The build command is a device build command, and @buildType@ is
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR'
--     or
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR'
--
-- -   For 'MicromapBuildInfoEXT':
--
--     -   Its @type@, and @flags@ members are equal to @pBuildInfo->type@
--         and @pBuildInfo->flags@, respectively.
--
--     -   The sum of usage information in either @pUsageCounts@ or
--         @ppUsageCounts@ is equal to the sum of usage information in
--         either @pBuildInfo->pUsageCounts@ or
--         @pBuildInfo->ppUsageCounts@.
--
-- Similarly, the @buildScratchSize@ value will support any build command
-- specifying the 'BUILD_MICROMAP_MODE_BUILD_EXT' @mode@ under the above
-- conditions.
--
-- == Valid Usage
--
-- -   #VUID-vkGetMicromapBuildSizesEXT-micromap-07439# The
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromap micromap>
--     feature /must/ be enabled
--
-- -   #VUID-vkGetMicromapBuildSizesEXT-device-07440# If @device@ was
--     created with multiple physical devices, then the
--     <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-bufferDeviceAddressMultiDevice bufferDeviceAddressMultiDevice>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkGetMicromapBuildSizesEXT-device-parameter# @device@ /must/
--     be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkGetMicromapBuildSizesEXT-buildType-parameter# @buildType@
--     /must/ be a valid
--     'Vulkan.Extensions.VK_KHR_acceleration_structure.AccelerationStructureBuildTypeKHR'
--     value
--
-- -   #VUID-vkGetMicromapBuildSizesEXT-pBuildInfo-parameter# @pBuildInfo@
--     /must/ be a valid pointer to a valid 'MicromapBuildInfoEXT'
--     structure
--
-- -   #VUID-vkGetMicromapBuildSizesEXT-pSizeInfo-parameter# @pSizeInfo@
--     /must/ be a valid pointer to a 'MicromapBuildSizesInfoEXT' structure
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.AccelerationStructureBuildTypeKHR',
-- 'Vulkan.Core10.Handles.Device', 'MicromapBuildInfoEXT',
-- 'MicromapBuildSizesInfoEXT'
getMicromapBuildSizesEXT :: forall io
                          . (MonadIO io)
                         => -- | @device@ is the logical device that will be used for creating the
                            -- micromap.
                            Device
                         -> -- | @buildType@ defines whether host or device operations (or both) are
                            -- being queried for.
                            AccelerationStructureBuildTypeKHR
                         -> -- | @pBuildInfo@ is a pointer to a 'MicromapBuildInfoEXT' structure
                            -- describing parameters of a build operation.
                            MicromapBuildInfoEXT
                         -> io (("sizeInfo" ::: MicromapBuildSizesInfoEXT))
getMicromapBuildSizesEXT :: forall (io :: * -> *).
MonadIO io =>
Device
-> AccelerationStructureBuildTypeKHR
-> MicromapBuildInfoEXT
-> io MicromapBuildSizesInfoEXT
getMicromapBuildSizesEXT Device
device AccelerationStructureBuildTypeKHR
buildType MicromapBuildInfoEXT
buildInfo = IO MicromapBuildSizesInfoEXT -> io MicromapBuildSizesInfoEXT
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MicromapBuildSizesInfoEXT -> io MicromapBuildSizesInfoEXT)
-> (ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT
    -> IO MicromapBuildSizesInfoEXT)
-> ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT
-> io MicromapBuildSizesInfoEXT
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT
-> IO MicromapBuildSizesInfoEXT
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT
 -> io MicromapBuildSizesInfoEXT)
-> ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT
-> io MicromapBuildSizesInfoEXT
forall a b. (a -> b) -> a -> b
$ do
  let vkGetMicromapBuildSizesEXTPtr :: FunPtr
  (Ptr Device_T
   -> AccelerationStructureBuildTypeKHR
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
   -> IO ())
vkGetMicromapBuildSizesEXTPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> AccelerationStructureBuildTypeKHR
      -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
      -> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
      -> IO ())
pVkGetMicromapBuildSizesEXT (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT MicromapBuildSizesInfoEXT IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT MicromapBuildSizesInfoEXT IO ())
-> IO () -> ContT MicromapBuildSizesInfoEXT IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> AccelerationStructureBuildTypeKHR
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
   -> IO ())
vkGetMicromapBuildSizesEXTPtr FunPtr
  (Ptr Device_T
   -> AccelerationStructureBuildTypeKHR
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> AccelerationStructureBuildTypeKHR
      -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
      -> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> AccelerationStructureBuildTypeKHR
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (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 String
"" String
"The function pointer for vkGetMicromapBuildSizesEXT is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetMicromapBuildSizesEXT' :: Ptr Device_T
-> AccelerationStructureBuildTypeKHR
-> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> IO ()
vkGetMicromapBuildSizesEXT' = FunPtr
  (Ptr Device_T
   -> AccelerationStructureBuildTypeKHR
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
   -> IO ())
-> Ptr Device_T
-> AccelerationStructureBuildTypeKHR
-> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> IO ()
mkVkGetMicromapBuildSizesEXT FunPtr
  (Ptr Device_T
   -> AccelerationStructureBuildTypeKHR
   -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
   -> IO ())
vkGetMicromapBuildSizesEXTPtr
  "pInfos" ::: Ptr MicromapBuildInfoEXT
pBuildInfo <- ((("pInfos" ::: Ptr MicromapBuildInfoEXT)
  -> IO MicromapBuildSizesInfoEXT)
 -> IO MicromapBuildSizesInfoEXT)
-> ContT
     MicromapBuildSizesInfoEXT
     IO
     ("pInfos" ::: Ptr MicromapBuildInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInfos" ::: Ptr MicromapBuildInfoEXT)
   -> IO MicromapBuildSizesInfoEXT)
  -> IO MicromapBuildSizesInfoEXT)
 -> ContT
      MicromapBuildSizesInfoEXT
      IO
      ("pInfos" ::: Ptr MicromapBuildInfoEXT))
-> ((("pInfos" ::: Ptr MicromapBuildInfoEXT)
     -> IO MicromapBuildSizesInfoEXT)
    -> IO MicromapBuildSizesInfoEXT)
-> ContT
     MicromapBuildSizesInfoEXT
     IO
     ("pInfos" ::: Ptr MicromapBuildInfoEXT)
forall a b. (a -> b) -> a -> b
$ MicromapBuildInfoEXT
-> (("pInfos" ::: Ptr MicromapBuildInfoEXT)
    -> IO MicromapBuildSizesInfoEXT)
-> IO MicromapBuildSizesInfoEXT
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MicromapBuildInfoEXT
buildInfo)
  "pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
pPSizeInfo <- ((("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
  -> IO MicromapBuildSizesInfoEXT)
 -> IO MicromapBuildSizesInfoEXT)
-> ContT
     MicromapBuildSizesInfoEXT
     IO
     ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @MicromapBuildSizesInfoEXT)
  IO () -> ContT MicromapBuildSizesInfoEXT IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT MicromapBuildSizesInfoEXT IO ())
-> IO () -> ContT MicromapBuildSizesInfoEXT IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetMicromapBuildSizesEXT" (Ptr Device_T
-> AccelerationStructureBuildTypeKHR
-> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> IO ()
vkGetMicromapBuildSizesEXT'
                                                          (Device -> Ptr Device_T
deviceHandle (Device
device))
                                                          (AccelerationStructureBuildTypeKHR
buildType)
                                                          "pInfos" ::: Ptr MicromapBuildInfoEXT
pBuildInfo
                                                          ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
pPSizeInfo))
  MicromapBuildSizesInfoEXT
pSizeInfo <- IO MicromapBuildSizesInfoEXT
-> ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO MicromapBuildSizesInfoEXT
 -> ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT)
-> IO MicromapBuildSizesInfoEXT
-> ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT
forall a b. (a -> b) -> a -> b
$ forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @MicromapBuildSizesInfoEXT "pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
pPSizeInfo
  MicromapBuildSizesInfoEXT
-> ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MicromapBuildSizesInfoEXT
 -> ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT)
-> MicromapBuildSizesInfoEXT
-> ContT MicromapBuildSizesInfoEXT IO MicromapBuildSizesInfoEXT
forall a b. (a -> b) -> a -> b
$ (MicromapBuildSizesInfoEXT
pSizeInfo)


-- | VkMicromapBuildInfoEXT - Structure specifying the data used to build a
-- micromap
--
-- = Description
--
-- Only one of @pUsageCounts@ or @ppUsageCounts@ /can/ be a valid pointer,
-- the other /must/ be @NULL@. The elements of the non-@NULL@ array
-- describe the total counts used to build each micromap. Each element
-- contains a @count@ which is the number of micromap triangles of that
-- @format@ and @subdivisionLevel@ contained in the micromap. Multiple
-- elements with the same @format@ and @subdivisionLevel@ are allowed and
-- the total count for that @format@ and @subdivisionLevel@ is the sum of
-- the @count@ for each element.
--
-- Each micromap triangle refers to one element in @triangleArray@ which
-- contains the @format@ and @subdivisionLevel@ for that particular
-- triangle as well as a @dataOffset@ in bytes which is the location
-- relative to @data@ where that triangle’s micromap data begins. The data
-- at @triangleArray@ is laid out as a 4 byte unsigned integer for the
-- @dataOffset@ followed by a 2 byte unsigned integer for the subdivision
-- level then a 2 byte unsigned integer for the format. In practice,
-- compilers compile 'MicromapTriangleEXT' to match this pattern.
--
-- The data at @data@ is packed as either one bit per element for
-- 'OPACITY_MICROMAP_FORMAT_2_STATE_EXT' or two bits per element for
-- 'OPACITY_MICROMAP_FORMAT_4_STATE_EXT' and is packed from LSB to MSB in
-- each byte. The data at each index in those bytes is interpreted as
-- discussed in
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#ray-opacity-micromap Ray Opacity Micromap>.
--
-- == Valid Usage
--
-- -   #VUID-VkMicromapBuildInfoEXT-pUsageCounts-07516# Only one of
--     @pUsageCounts@ or @ppUsageCounts@ /can/ be a valid pointer, the
--     other /must/ be @NULL@.
--
-- -   #VUID-VkMicromapBuildInfoEXT-type-07517# If @type@ is
--     'MICROMAP_TYPE_OPACITY_MICROMAP_EXT' the @format@ member of
--     'MicromapUsageEXT' /must/ be a valid value from
--     'OpacityMicromapFormatEXT'
--
-- -   #VUID-VkMicromapBuildInfoEXT-type-07518# If @type@ is
--     'MICROMAP_TYPE_OPACITY_MICROMAP_EXT' the @format@ member of
--     'MicromapTriangleEXT' /must/ be a valid value from
--     'OpacityMicromapFormatEXT'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkMicromapBuildInfoEXT-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MICROMAP_BUILD_INFO_EXT'
--
-- -   #VUID-VkMicromapBuildInfoEXT-pNext-pNext# @pNext@ /must/ be @NULL@
--
-- -   #VUID-VkMicromapBuildInfoEXT-type-parameter# @type@ /must/ be a
--     valid 'MicromapTypeEXT' value
--
-- -   #VUID-VkMicromapBuildInfoEXT-flags-parameter# @flags@ /must/ be a
--     valid combination of 'BuildMicromapFlagBitsEXT' values
--
-- -   #VUID-VkMicromapBuildInfoEXT-pUsageCounts-parameter# If
--     @usageCountsCount@ is not @0@, and @pUsageCounts@ is not @NULL@,
--     @pUsageCounts@ /must/ be a valid pointer to an array of
--     @usageCountsCount@ 'MicromapUsageEXT' structures
--
-- -   #VUID-VkMicromapBuildInfoEXT-ppUsageCounts-parameter# If
--     @usageCountsCount@ is not @0@, and @ppUsageCounts@ is not @NULL@,
--     @ppUsageCounts@ /must/ be a valid pointer to an array of
--     @usageCountsCount@ valid pointers to 'MicromapUsageEXT' structures
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'BuildMicromapFlagsEXT', 'BuildMicromapModeEXT',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.DeviceOrHostAddressConstKHR',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.DeviceOrHostAddressKHR',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Extensions.Handles.MicromapEXT', 'MicromapTypeEXT',
-- 'MicromapUsageEXT', 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'buildMicromapsEXT', 'cmdBuildMicromapsEXT', 'getMicromapBuildSizesEXT'
data MicromapBuildInfoEXT = MicromapBuildInfoEXT
  { -- | @type@ is a 'MicromapTypeEXT' value specifying the type of micromap
    -- being built.
    MicromapBuildInfoEXT -> MicromapTypeEXT
type' :: MicromapTypeEXT
  , -- | @flags@ is a bitmask of 'BuildMicromapFlagBitsEXT' specifying additional
    -- parameters of the micromap.
    MicromapBuildInfoEXT -> BuildMicromapFlagBitsEXT
flags :: BuildMicromapFlagsEXT
  , -- | @mode@ is a 'BuildMicromapModeEXT' value specifying the type of
    -- operation to perform.
    MicromapBuildInfoEXT -> BuildMicromapModeEXT
mode :: BuildMicromapModeEXT
  , -- | @dstMicromap@ is a pointer to the target micromap for the build.
    MicromapBuildInfoEXT -> MicromapEXT
dstMicromap :: MicromapEXT
  , -- | @usageCountsCount@ specifies the number of usage counts structures that
    -- will be used to determine the size of this micromap.
    MicromapBuildInfoEXT -> Flags
usageCountsCount :: Word32
  , -- | @pUsageCounts@ is a pointer to an array of 'MicromapUsageEXT'
    -- structures.
    MicromapBuildInfoEXT -> Vector MicromapUsageEXT
usageCounts :: Vector MicromapUsageEXT
  , -- | @data@ is the device or host address to memory which contains the data
    -- for the micromap.
    MicromapBuildInfoEXT -> DeviceOrHostAddressConstKHR
data' :: DeviceOrHostAddressConstKHR
  , -- | @scratchData@ is the device or host address to memory that will be used
    -- as scratch memory for the build.
    MicromapBuildInfoEXT -> DeviceOrHostAddressKHR
scratchData :: DeviceOrHostAddressKHR
  , -- | @triangleArray@ is the device or host address to memory containing the
    -- 'MicromapTriangleEXT' data
    MicromapBuildInfoEXT -> DeviceOrHostAddressConstKHR
triangleArray :: DeviceOrHostAddressConstKHR
  , -- | @triangleArrayStride@ is the stride in bytes between each element of
    -- @triangleArray@
    MicromapBuildInfoEXT -> "dataSize" ::: Word64
triangleArrayStride :: DeviceSize
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MicromapBuildInfoEXT)
#endif
deriving instance Show MicromapBuildInfoEXT

instance ToCStruct MicromapBuildInfoEXT where
  withCStruct :: forall b.
MicromapBuildInfoEXT
-> (("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO b) -> IO b
withCStruct MicromapBuildInfoEXT
x ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO b
f = Int -> (("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
96 ((("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO b) -> IO b)
-> (("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \"pInfos" ::: Ptr MicromapBuildInfoEXT
p -> ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> MicromapBuildInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfos" ::: Ptr MicromapBuildInfoEXT
p MicromapBuildInfoEXT
x (("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO b
f "pInfos" ::: Ptr MicromapBuildInfoEXT
p)
  pokeCStruct :: forall b.
("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> MicromapBuildInfoEXT -> IO b -> IO b
pokeCStruct "pInfos" ::: Ptr MicromapBuildInfoEXT
p MicromapBuildInfoEXT{Flags
"dataSize" ::: Word64
Vector MicromapUsageEXT
MicromapEXT
DeviceOrHostAddressConstKHR
DeviceOrHostAddressKHR
BuildMicromapModeEXT
BuildMicromapFlagBitsEXT
MicromapTypeEXT
triangleArrayStride :: "dataSize" ::: Word64
triangleArray :: DeviceOrHostAddressConstKHR
scratchData :: DeviceOrHostAddressKHR
data' :: DeviceOrHostAddressConstKHR
usageCounts :: Vector MicromapUsageEXT
usageCountsCount :: Flags
dstMicromap :: MicromapEXT
mode :: BuildMicromapModeEXT
flags :: BuildMicromapFlagBitsEXT
type' :: MicromapTypeEXT
$sel:triangleArrayStride:MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> "dataSize" ::: Word64
$sel:triangleArray:MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> DeviceOrHostAddressConstKHR
$sel:scratchData:MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> DeviceOrHostAddressKHR
$sel:data':MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> DeviceOrHostAddressConstKHR
$sel:usageCounts:MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> Vector MicromapUsageEXT
$sel:usageCountsCount:MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> Flags
$sel:dstMicromap:MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> MicromapEXT
$sel:mode:MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> BuildMicromapModeEXT
$sel:flags:MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> BuildMicromapFlagBitsEXT
$sel:type':MicromapBuildInfoEXT :: MicromapBuildInfoEXT -> MicromapTypeEXT
..} IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MICROMAP_BUILD_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr MicromapTypeEXT -> MicromapTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr MicromapTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MicromapTypeEXT)) (MicromapTypeEXT
type')
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr BuildMicromapFlagBitsEXT -> BuildMicromapFlagBitsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr BuildMicromapFlagBitsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr BuildMicromapFlagsEXT)) (BuildMicromapFlagBitsEXT
flags)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr BuildMicromapModeEXT -> BuildMicromapModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr BuildMicromapModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BuildMicromapModeEXT)) (BuildMicromapModeEXT
mode)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr MicromapEXT)) (MicromapEXT
dstMicromap)
    let pUsageCountsLength :: Int
pUsageCountsLength = Vector MicromapUsageEXT -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector MicromapUsageEXT -> Int) -> Vector MicromapUsageEXT -> Int
forall a b. (a -> b) -> a -> b
$ (Vector MicromapUsageEXT
usageCounts)
    Flags
usageCountsCount'' <- IO Flags -> ContT b IO Flags
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Flags -> ContT b IO Flags) -> IO Flags -> ContT b IO Flags
forall a b. (a -> b) -> a -> b
$ if (Flags
usageCountsCount) Flags -> Flags -> Bool
forall a. Eq a => a -> a -> Bool
== Flags
0
      then Flags -> IO Flags
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> IO Flags) -> Flags -> IO Flags
forall a b. (a -> b) -> a -> b
$ Int -> Flags
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pUsageCountsLength
      else do
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int -> Flags
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pUsageCountsLength Flags -> Flags -> Bool
forall a. Eq a => a -> a -> Bool
== (Flags
usageCountsCount) Bool -> Bool -> Bool
|| Int
pUsageCountsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (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 String
"" String
"pUsageCounts must be empty or have 'usageCountsCount' elements" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
        Flags -> IO Flags
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags
usageCountsCount)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word32)) (Flags
usageCountsCount'')
    Ptr MicromapUsageEXT
pUsageCounts'' <- if Vector MicromapUsageEXT -> Bool
forall a. Vector a -> Bool
Data.Vector.null (Vector MicromapUsageEXT
usageCounts)
      then Ptr MicromapUsageEXT -> ContT b IO (Ptr MicromapUsageEXT)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr MicromapUsageEXT
forall a. Ptr a
nullPtr
      else do
        Ptr MicromapUsageEXT
pPUsageCounts <- ((Ptr MicromapUsageEXT -> IO b) -> IO b)
-> ContT b IO (Ptr MicromapUsageEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr MicromapUsageEXT -> IO b) -> IO b)
 -> ContT b IO (Ptr MicromapUsageEXT))
-> ((Ptr MicromapUsageEXT -> IO b) -> IO b)
-> ContT b IO (Ptr MicromapUsageEXT)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @MicromapUsageEXT (((Vector MicromapUsageEXT -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector MicromapUsageEXT
usageCounts))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
12)
        IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> MicromapUsageEXT -> IO ())
-> Vector MicromapUsageEXT -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i MicromapUsageEXT
e -> Ptr MicromapUsageEXT -> MicromapUsageEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MicromapUsageEXT
pPUsageCounts Ptr MicromapUsageEXT -> Int -> Ptr MicromapUsageEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MicromapUsageEXT) (MicromapUsageEXT
e)) ((Vector MicromapUsageEXT
usageCounts))
        Ptr MicromapUsageEXT -> ContT b IO (Ptr MicromapUsageEXT)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr MicromapUsageEXT -> ContT b IO (Ptr MicromapUsageEXT))
-> Ptr MicromapUsageEXT -> ContT b IO (Ptr MicromapUsageEXT)
forall a b. (a -> b) -> a -> b
$ Ptr MicromapUsageEXT
pPUsageCounts
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr MicromapUsageEXT) -> Ptr MicromapUsageEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr (Ptr MicromapUsageEXT)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr (Ptr MicromapUsageEXT))) Ptr MicromapUsageEXT
pUsageCounts''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (Ptr MicromapUsageEXT))
-> Ptr (Ptr MicromapUsageEXT) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr (Ptr (Ptr MicromapUsageEXT))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr (Ptr (Ptr MicromapUsageEXT)))) (Ptr (Ptr MicromapUsageEXT)
forall a. Ptr a
nullPtr)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
data') (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressKHR
-> DeviceOrHostAddressKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr DeviceOrHostAddressKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr DeviceOrHostAddressKHR)) (DeviceOrHostAddressKHR
scratchData) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
triangleArray) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr DeviceSize)) ("dataSize" ::: Word64
triangleArrayStride)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
96
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pInfos" ::: Ptr MicromapBuildInfoEXT
p IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MICROMAP_BUILD_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr MicromapTypeEXT -> MicromapTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr MicromapTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MicromapTypeEXT)) (MicromapTypeEXT
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr BuildMicromapModeEXT -> BuildMicromapModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr BuildMicromapModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr BuildMicromapModeEXT)) (BuildMicromapModeEXT
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (Ptr MicromapUsageEXT))
-> Ptr (Ptr MicromapUsageEXT) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr (Ptr (Ptr MicromapUsageEXT))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr (Ptr (Ptr MicromapUsageEXT)))) (Ptr (Ptr MicromapUsageEXT)
forall a. Ptr a
nullPtr)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressKHR
-> DeviceOrHostAddressKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr DeviceOrHostAddressKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
72 :: Ptr DeviceOrHostAddressKHR)) (DeviceOrHostAddressKHR
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
80 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfos" ::: Ptr MicromapBuildInfoEXT
p ("pInfos" ::: Ptr MicromapBuildInfoEXT)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
88 :: Ptr DeviceSize)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance Zero MicromapBuildInfoEXT where
  zero :: MicromapBuildInfoEXT
zero = MicromapTypeEXT
-> BuildMicromapFlagBitsEXT
-> BuildMicromapModeEXT
-> MicromapEXT
-> Flags
-> Vector MicromapUsageEXT
-> DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressKHR
-> DeviceOrHostAddressConstKHR
-> ("dataSize" ::: Word64)
-> MicromapBuildInfoEXT
MicromapBuildInfoEXT
           MicromapTypeEXT
forall a. Zero a => a
zero
           BuildMicromapFlagBitsEXT
forall a. Zero a => a
zero
           BuildMicromapModeEXT
forall a. Zero a => a
zero
           MicromapEXT
forall a. Zero a => a
zero
           Flags
forall a. Zero a => a
zero
           Vector MicromapUsageEXT
forall a. Monoid a => a
mempty
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero
           DeviceOrHostAddressKHR
forall a. Zero a => a
zero
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero


-- | VkMicromapCreateInfoEXT - Structure specifying the parameters of a newly
-- created micromap object
--
-- = Description
--
-- If @deviceAddress@ is zero, no specific address is requested.
--
-- If @deviceAddress@ is not zero, @deviceAddress@ /must/ be an address
-- retrieved from an identically created micromap on the same
-- implementation. The micromap /must/ also be placed on an identically
-- created @buffer@ and at the same @offset@.
--
-- Applications /should/ avoid creating micromaps with application-provided
-- addresses and implementation-provided addresses in the same process, to
-- reduce the likelihood of
-- 'Vulkan.Extensions.VK_KHR_buffer_device_address.ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS_KHR'
-- errors.
--
-- Note
--
-- The expected usage for this is that a trace capture\/replay tool will
-- add the
-- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT'
-- flag to all buffers that use
-- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_SHADER_DEVICE_ADDRESS_BIT',
-- and will add
-- 'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_SHADER_DEVICE_ADDRESS_BIT'
-- to all buffers used as storage for a micromap where @deviceAddress@ is
-- not zero. This also means that the tool will need to add
-- 'Vulkan.Core11.Enums.MemoryAllocateFlagBits.MEMORY_ALLOCATE_DEVICE_ADDRESS_BIT'
-- to memory allocations to allow the flag to be set where the application
-- may not have otherwise required it. During capture the tool will save
-- the queried opaque device addresses in the trace. During replay, the
-- buffers will be created specifying the original address so any address
-- values stored in the trace data will remain valid.
--
-- Implementations are expected to separate such buffers in the GPU address
-- space so normal allocations will avoid using these addresses.
-- Apps\/tools should avoid mixing app-provided and implementation-provided
-- addresses for buffers created with
-- 'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT',
-- to avoid address space allocation conflicts.
--
-- If the micromap will be the target of a build operation, the required
-- size for a micromap /can/ be queried with 'getMicromapBuildSizesEXT'.
--
-- == Valid Usage
--
-- -   #VUID-VkMicromapCreateInfoEXT-deviceAddress-07433# If
--     @deviceAddress@ is not zero, @createFlags@ /must/ include
--     'MICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT'
--
-- -   #VUID-VkMicromapCreateInfoEXT-createFlags-07434# If @createFlags@
--     includes 'MICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT',
--     'PhysicalDeviceOpacityMicromapFeaturesEXT'::@micromapCaptureReplay@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- -   #VUID-VkMicromapCreateInfoEXT-buffer-07435# @buffer@ /must/ have
--     been created with a @usage@ value containing
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_MICROMAP_STORAGE_BIT_EXT'
--
-- -   #VUID-VkMicromapCreateInfoEXT-buffer-07436# @buffer@ /must/ not have
--     been created with
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
--
-- -   #VUID-VkMicromapCreateInfoEXT-offset-07437# The sum of @offset@ and
--     @size@ /must/ be less than the size of @buffer@
--
-- -   #VUID-VkMicromapCreateInfoEXT-offset-07438# @offset@ /must/ be a
--     multiple of @256@ bytes
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkMicromapCreateInfoEXT-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_MICROMAP_CREATE_INFO_EXT'
--
-- -   #VUID-VkMicromapCreateInfoEXT-pNext-pNext# @pNext@ /must/ be @NULL@
--
-- -   #VUID-VkMicromapCreateInfoEXT-createFlags-parameter# @createFlags@
--     /must/ be a valid combination of 'MicromapCreateFlagBitsEXT' values
--
-- -   #VUID-VkMicromapCreateInfoEXT-buffer-parameter# @buffer@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   #VUID-VkMicromapCreateInfoEXT-type-parameter# @type@ /must/ be a
--     valid 'MicromapTypeEXT' value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.Handles.Buffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceAddress',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize', 'MicromapCreateFlagsEXT',
-- 'MicromapTypeEXT', 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'createMicromapEXT'
data MicromapCreateInfoEXT = MicromapCreateInfoEXT
  { -- | @createFlags@ is a bitmask of 'MicromapCreateFlagBitsEXT' specifying
    -- additional creation parameters of the micromap.
    MicromapCreateInfoEXT -> MicromapCreateFlagBitsEXT
createFlags :: MicromapCreateFlagsEXT
  , -- | @buffer@ is the buffer on which the micromap will be stored.
    MicromapCreateInfoEXT -> Buffer
buffer :: Buffer
  , -- | @offset@ is an offset in bytes from the base address of the buffer at
    -- which the micromap will be stored, and /must/ be a multiple of @256@.
    MicromapCreateInfoEXT -> "dataSize" ::: Word64
offset :: DeviceSize
  , -- | @size@ is the size required for the micromap.
    MicromapCreateInfoEXT -> "dataSize" ::: Word64
size :: DeviceSize
  , -- | @type@ is a 'MicromapTypeEXT' value specifying the type of micromap that
    -- will be created.
    MicromapCreateInfoEXT -> MicromapTypeEXT
type' :: MicromapTypeEXT
  , -- | @deviceAddress@ is the device address requested for the micromap if the
    -- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#features-micromapCaptureReplay micromapCaptureReplay>
    -- feature is being used.
    MicromapCreateInfoEXT -> "dataSize" ::: Word64
deviceAddress :: DeviceAddress
  }
  deriving (Typeable, MicromapCreateInfoEXT -> MicromapCreateInfoEXT -> Bool
(MicromapCreateInfoEXT -> MicromapCreateInfoEXT -> Bool)
-> (MicromapCreateInfoEXT -> MicromapCreateInfoEXT -> Bool)
-> Eq MicromapCreateInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MicromapCreateInfoEXT -> MicromapCreateInfoEXT -> Bool
$c/= :: MicromapCreateInfoEXT -> MicromapCreateInfoEXT -> Bool
== :: MicromapCreateInfoEXT -> MicromapCreateInfoEXT -> Bool
$c== :: MicromapCreateInfoEXT -> MicromapCreateInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MicromapCreateInfoEXT)
#endif
deriving instance Show MicromapCreateInfoEXT

instance ToCStruct MicromapCreateInfoEXT where
  withCStruct :: forall b.
MicromapCreateInfoEXT
-> (Ptr MicromapCreateInfoEXT -> IO b) -> IO b
withCStruct MicromapCreateInfoEXT
x Ptr MicromapCreateInfoEXT -> IO b
f = Int -> (Ptr MicromapCreateInfoEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
64 ((Ptr MicromapCreateInfoEXT -> IO b) -> IO b)
-> (Ptr MicromapCreateInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr MicromapCreateInfoEXT
p -> Ptr MicromapCreateInfoEXT -> MicromapCreateInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MicromapCreateInfoEXT
p MicromapCreateInfoEXT
x (Ptr MicromapCreateInfoEXT -> IO b
f Ptr MicromapCreateInfoEXT
p)
  pokeCStruct :: forall b.
Ptr MicromapCreateInfoEXT -> MicromapCreateInfoEXT -> IO b -> IO b
pokeCStruct Ptr MicromapCreateInfoEXT
p MicromapCreateInfoEXT{"dataSize" ::: Word64
Buffer
MicromapCreateFlagBitsEXT
MicromapTypeEXT
deviceAddress :: "dataSize" ::: Word64
type' :: MicromapTypeEXT
size :: "dataSize" ::: Word64
offset :: "dataSize" ::: Word64
buffer :: Buffer
createFlags :: MicromapCreateFlagBitsEXT
$sel:deviceAddress:MicromapCreateInfoEXT :: MicromapCreateInfoEXT -> "dataSize" ::: Word64
$sel:type':MicromapCreateInfoEXT :: MicromapCreateInfoEXT -> MicromapTypeEXT
$sel:size:MicromapCreateInfoEXT :: MicromapCreateInfoEXT -> "dataSize" ::: Word64
$sel:offset:MicromapCreateInfoEXT :: MicromapCreateInfoEXT -> "dataSize" ::: Word64
$sel:buffer:MicromapCreateInfoEXT :: MicromapCreateInfoEXT -> Buffer
$sel:createFlags:MicromapCreateInfoEXT :: MicromapCreateInfoEXT -> MicromapCreateFlagBitsEXT
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MICROMAP_CREATE_INFO_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr MicromapCreateFlagBitsEXT -> MicromapCreateFlagBitsEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr MicromapCreateFlagBitsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MicromapCreateFlagsEXT)) (MicromapCreateFlagBitsEXT
createFlags)
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Buffer)) (Buffer
buffer)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) ("dataSize" ::: Word64
offset)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize)) ("dataSize" ::: Word64
size)
    Ptr MicromapTypeEXT -> MicromapTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr MicromapTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr MicromapTypeEXT)) (MicromapTypeEXT
type')
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr DeviceAddress)) ("dataSize" ::: Word64
deviceAddress)
    IO b
f
  cStructSize :: Int
cStructSize = Int
64
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr MicromapCreateInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr MicromapCreateInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MICROMAP_CREATE_INFO_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Buffer)) (Buffer
forall a. Zero a => a
zero)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    Ptr MicromapTypeEXT -> MicromapTypeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr MicromapTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr MicromapTypeEXT)) (MicromapTypeEXT
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct MicromapCreateInfoEXT where
  peekCStruct :: Ptr MicromapCreateInfoEXT -> IO MicromapCreateInfoEXT
peekCStruct Ptr MicromapCreateInfoEXT
p = do
    MicromapCreateFlagBitsEXT
createFlags <- forall a. Storable a => Ptr a -> IO a
peek @MicromapCreateFlagsEXT ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr MicromapCreateFlagBitsEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MicromapCreateFlagsEXT))
    Buffer
buffer <- forall a. Storable a => Ptr a -> IO a
peek @Buffer ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Buffer))
    "dataSize" ::: Word64
offset <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize))
    "dataSize" ::: Word64
size <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr DeviceSize))
    MicromapTypeEXT
type' <- forall a. Storable a => Ptr a -> IO a
peek @MicromapTypeEXT ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr MicromapTypeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr MicromapTypeEXT))
    "dataSize" ::: Word64
deviceAddress <- forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress ((Ptr MicromapCreateInfoEXT
p Ptr MicromapCreateInfoEXT -> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr DeviceAddress))
    MicromapCreateInfoEXT -> IO MicromapCreateInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MicromapCreateInfoEXT -> IO MicromapCreateInfoEXT)
-> MicromapCreateInfoEXT -> IO MicromapCreateInfoEXT
forall a b. (a -> b) -> a -> b
$ MicromapCreateFlagBitsEXT
-> Buffer
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> MicromapTypeEXT
-> ("dataSize" ::: Word64)
-> MicromapCreateInfoEXT
MicromapCreateInfoEXT
             MicromapCreateFlagBitsEXT
createFlags Buffer
buffer "dataSize" ::: Word64
offset "dataSize" ::: Word64
size MicromapTypeEXT
type' "dataSize" ::: Word64
deviceAddress

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

instance Zero MicromapCreateInfoEXT where
  zero :: MicromapCreateInfoEXT
zero = MicromapCreateFlagBitsEXT
-> Buffer
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> MicromapTypeEXT
-> ("dataSize" ::: Word64)
-> MicromapCreateInfoEXT
MicromapCreateInfoEXT
           MicromapCreateFlagBitsEXT
forall a. Zero a => a
zero
           Buffer
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           MicromapTypeEXT
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero


-- | VkMicromapVersionInfoEXT - Micromap version information
--
-- = Description
--
-- Note
--
-- @pVersionData@ is a /pointer/ to an array of
-- 2×'Vulkan.Core10.APIConstants.UUID_SIZE' @uint8_t@ values instead of two
-- 'Vulkan.Core10.APIConstants.UUID_SIZE' arrays as the expected use case
-- for this member is to be pointed at the header of a previously
-- serialized micromap (via 'cmdCopyMicromapToMemoryEXT' or
-- 'copyMicromapToMemoryEXT') that is loaded in memory. Using arrays would
-- necessitate extra memory copies of the UUIDs.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getDeviceMicromapCompatibilityEXT'
data MicromapVersionInfoEXT = MicromapVersionInfoEXT
  { -- | @pVersionData@ is a pointer to the version header of a micromap as
    -- defined in 'cmdCopyMicromapToMemoryEXT'
    --
    -- #VUID-VkMicromapVersionInfoEXT-pVersionData-parameter# @pVersionData@
    -- /must/ be a valid pointer to an array of
    -- \(2 \times \mathtt{VK\_UUID\_SIZE}\) @uint8_t@ values
    MicromapVersionInfoEXT -> ByteString
versionData :: ByteString }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MicromapVersionInfoEXT)
#endif
deriving instance Show MicromapVersionInfoEXT

instance ToCStruct MicromapVersionInfoEXT where
  withCStruct :: forall b.
MicromapVersionInfoEXT
-> (Ptr MicromapVersionInfoEXT -> IO b) -> IO b
withCStruct MicromapVersionInfoEXT
x Ptr MicromapVersionInfoEXT -> IO b
f = Int -> (Ptr MicromapVersionInfoEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr MicromapVersionInfoEXT -> IO b) -> IO b)
-> (Ptr MicromapVersionInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr MicromapVersionInfoEXT
p -> Ptr MicromapVersionInfoEXT
-> MicromapVersionInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MicromapVersionInfoEXT
p MicromapVersionInfoEXT
x (Ptr MicromapVersionInfoEXT -> IO b
f Ptr MicromapVersionInfoEXT
p)
  pokeCStruct :: forall b.
Ptr MicromapVersionInfoEXT
-> MicromapVersionInfoEXT -> IO b -> IO b
pokeCStruct Ptr MicromapVersionInfoEXT
p MicromapVersionInfoEXT{ByteString
versionData :: ByteString
$sel:versionData:MicromapVersionInfoEXT :: MicromapVersionInfoEXT -> ByteString
..} IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapVersionInfoEXT
p Ptr MicromapVersionInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MICROMAP_VERSION_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapVersionInfoEXT
p Ptr MicromapVersionInfoEXT -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (ByteString -> Int
Data.ByteString.length (ByteString
versionData) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
forall a. Integral a => a
UUID_SIZE) (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 String
"" String
"VkMicromapVersionInfoEXT::versionData must be 2*VK_UUID_SIZE bytes" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    Ptr Word8
versionData' <- (Ptr CChar -> Ptr Word8)
-> ContT b IO (Ptr CChar) -> ContT b IO (Ptr Word8)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. Ptr a -> Ptr b
castPtr @CChar @Word8) (ContT b IO (Ptr CChar) -> ContT b IO (Ptr Word8))
-> (((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar))
-> ((Ptr CChar -> IO b) -> IO b)
-> ContT b IO (Ptr Word8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr CChar)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr Word8))
-> ((Ptr CChar -> IO b) -> IO b) -> ContT b IO (Ptr Word8)
forall a b. (a -> b) -> a -> b
$ ByteString -> (Ptr CChar -> IO b) -> IO b
forall a. ByteString -> (Ptr CChar -> IO a) -> IO a
unsafeUseAsCString (ByteString
versionData)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Word8) -> Ptr Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapVersionInfoEXT
p Ptr MicromapVersionInfoEXT -> Int -> Ptr (Ptr Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr Word8))) Ptr Word8
versionData'
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr MicromapVersionInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr MicromapVersionInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapVersionInfoEXT
p Ptr MicromapVersionInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MICROMAP_VERSION_INFO_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapVersionInfoEXT
p Ptr MicromapVersionInfoEXT -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

instance FromCStruct MicromapVersionInfoEXT where
  peekCStruct :: Ptr MicromapVersionInfoEXT -> IO MicromapVersionInfoEXT
peekCStruct Ptr MicromapVersionInfoEXT
p = do
    Ptr Word8
versionData <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word8) ((Ptr MicromapVersionInfoEXT
p Ptr MicromapVersionInfoEXT -> Int -> Ptr (Ptr Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr (Ptr Word8)))
    ByteString
versionData' <- CStringLen -> IO ByteString
packCStringLen ( forall a b. Ptr a -> Ptr b
castPtr @Word8 @CChar Ptr Word8
versionData
                                   , Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
forall a. Integral a => a
UUID_SIZE )
    MicromapVersionInfoEXT -> IO MicromapVersionInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MicromapVersionInfoEXT -> IO MicromapVersionInfoEXT)
-> MicromapVersionInfoEXT -> IO MicromapVersionInfoEXT
forall a b. (a -> b) -> a -> b
$ ByteString -> MicromapVersionInfoEXT
MicromapVersionInfoEXT
             ByteString
versionData'

instance Zero MicromapVersionInfoEXT where
  zero :: MicromapVersionInfoEXT
zero = ByteString -> MicromapVersionInfoEXT
MicromapVersionInfoEXT
           ByteString
forall a. Monoid a => a
mempty


-- | VkCopyMicromapInfoEXT - Parameters for copying a micromap
--
-- == Valid Usage
--
-- -   #VUID-VkCopyMicromapInfoEXT-mode-07531# @mode@ /must/ be
--     'COPY_MICROMAP_MODE_COMPACT_EXT' or 'COPY_MICROMAP_MODE_CLONE_EXT'
--
-- -   #VUID-VkCopyMicromapInfoEXT-src-07532# The source acceleration
--     structure @src@ /must/ have been constructed prior to the execution
--     of this command
--
-- -   #VUID-VkCopyMicromapInfoEXT-mode-07533# If @mode@ is
--     'COPY_MICROMAP_MODE_COMPACT_EXT', @src@ /must/ have been constructed
--     with 'BUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT' in the build
--
-- -   #VUID-VkCopyMicromapInfoEXT-buffer-07534# The @buffer@ used to
--     create @src@ /must/ be bound to device memory
--
-- -   #VUID-VkCopyMicromapInfoEXT-buffer-07535# The @buffer@ used to
--     create @dst@ /must/ be bound to device memory
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkCopyMicromapInfoEXT-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COPY_MICROMAP_INFO_EXT'
--
-- -   #VUID-VkCopyMicromapInfoEXT-pNext-pNext# @pNext@ /must/ be @NULL@
--
-- -   #VUID-VkCopyMicromapInfoEXT-src-parameter# @src@ /must/ be a valid
--     'Vulkan.Extensions.Handles.MicromapEXT' handle
--
-- -   #VUID-VkCopyMicromapInfoEXT-dst-parameter# @dst@ /must/ be a valid
--     'Vulkan.Extensions.Handles.MicromapEXT' handle
--
-- -   #VUID-VkCopyMicromapInfoEXT-mode-parameter# @mode@ /must/ be a valid
--     'CopyMicromapModeEXT' value
--
-- -   #VUID-VkCopyMicromapInfoEXT-commonparent# Both of @dst@, and @src@
--     /must/ have been created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'CopyMicromapModeEXT', 'Vulkan.Extensions.Handles.MicromapEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'cmdCopyMicromapEXT',
-- 'copyMicromapEXT'
data CopyMicromapInfoEXT = CopyMicromapInfoEXT
  { -- | @src@ is the source micromap for the copy.
    CopyMicromapInfoEXT -> MicromapEXT
src :: MicromapEXT
  , -- | @dst@ is the target micromap for the copy.
    CopyMicromapInfoEXT -> MicromapEXT
dst :: MicromapEXT
  , -- | @mode@ is a 'CopyMicromapModeEXT' value specifying additional operations
    -- to perform during the copy.
    CopyMicromapInfoEXT -> CopyMicromapModeEXT
mode :: CopyMicromapModeEXT
  }
  deriving (Typeable, CopyMicromapInfoEXT -> CopyMicromapInfoEXT -> Bool
(CopyMicromapInfoEXT -> CopyMicromapInfoEXT -> Bool)
-> (CopyMicromapInfoEXT -> CopyMicromapInfoEXT -> Bool)
-> Eq CopyMicromapInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyMicromapInfoEXT -> CopyMicromapInfoEXT -> Bool
$c/= :: CopyMicromapInfoEXT -> CopyMicromapInfoEXT -> Bool
== :: CopyMicromapInfoEXT -> CopyMicromapInfoEXT -> Bool
$c== :: CopyMicromapInfoEXT -> CopyMicromapInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CopyMicromapInfoEXT)
#endif
deriving instance Show CopyMicromapInfoEXT

instance ToCStruct CopyMicromapInfoEXT where
  withCStruct :: forall b.
CopyMicromapInfoEXT -> (Ptr CopyMicromapInfoEXT -> IO b) -> IO b
withCStruct CopyMicromapInfoEXT
x Ptr CopyMicromapInfoEXT -> IO b
f = Int -> (Ptr CopyMicromapInfoEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((Ptr CopyMicromapInfoEXT -> IO b) -> IO b)
-> (Ptr CopyMicromapInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr CopyMicromapInfoEXT
p -> Ptr CopyMicromapInfoEXT -> CopyMicromapInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CopyMicromapInfoEXT
p CopyMicromapInfoEXT
x (Ptr CopyMicromapInfoEXT -> IO b
f Ptr CopyMicromapInfoEXT
p)
  pokeCStruct :: forall b.
Ptr CopyMicromapInfoEXT -> CopyMicromapInfoEXT -> IO b -> IO b
pokeCStruct Ptr CopyMicromapInfoEXT
p CopyMicromapInfoEXT{MicromapEXT
CopyMicromapModeEXT
mode :: CopyMicromapModeEXT
dst :: MicromapEXT
src :: MicromapEXT
$sel:mode:CopyMicromapInfoEXT :: CopyMicromapInfoEXT -> CopyMicromapModeEXT
$sel:dst:CopyMicromapInfoEXT :: CopyMicromapInfoEXT -> MicromapEXT
$sel:src:CopyMicromapInfoEXT :: CopyMicromapInfoEXT -> MicromapEXT
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_MICROMAP_INFO_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MicromapEXT)) (MicromapEXT
src)
    ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr MicromapEXT)) (MicromapEXT
dst)
    Ptr CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> Ptr CopyMicromapModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CopyMicromapModeEXT)) (CopyMicromapModeEXT
mode)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr CopyMicromapInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr CopyMicromapInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_MICROMAP_INFO_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MicromapEXT)) (MicromapEXT
forall a. Zero a => a
zero)
    ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr MicromapEXT)) (MicromapEXT
forall a. Zero a => a
zero)
    Ptr CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> Ptr CopyMicromapModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CopyMicromapModeEXT)) (CopyMicromapModeEXT
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct CopyMicromapInfoEXT where
  peekCStruct :: Ptr CopyMicromapInfoEXT -> IO CopyMicromapInfoEXT
peekCStruct Ptr CopyMicromapInfoEXT
p = do
    MicromapEXT
src <- forall a. Storable a => Ptr a -> IO a
peek @MicromapEXT ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MicromapEXT))
    MicromapEXT
dst <- forall a. Storable a => Ptr a -> IO a
peek @MicromapEXT ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr MicromapEXT))
    CopyMicromapModeEXT
mode <- forall a. Storable a => Ptr a -> IO a
peek @CopyMicromapModeEXT ((Ptr CopyMicromapInfoEXT
p Ptr CopyMicromapInfoEXT -> Int -> Ptr CopyMicromapModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CopyMicromapModeEXT))
    CopyMicromapInfoEXT -> IO CopyMicromapInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CopyMicromapInfoEXT -> IO CopyMicromapInfoEXT)
-> CopyMicromapInfoEXT -> IO CopyMicromapInfoEXT
forall a b. (a -> b) -> a -> b
$ MicromapEXT
-> MicromapEXT -> CopyMicromapModeEXT -> CopyMicromapInfoEXT
CopyMicromapInfoEXT
             MicromapEXT
src MicromapEXT
dst CopyMicromapModeEXT
mode

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

instance Zero CopyMicromapInfoEXT where
  zero :: CopyMicromapInfoEXT
zero = MicromapEXT
-> MicromapEXT -> CopyMicromapModeEXT -> CopyMicromapInfoEXT
CopyMicromapInfoEXT
           MicromapEXT
forall a. Zero a => a
zero
           MicromapEXT
forall a. Zero a => a
zero
           CopyMicromapModeEXT
forall a. Zero a => a
zero


-- | VkCopyMicromapToMemoryInfoEXT - Parameters for serializing a micromap
--
-- == Valid Usage
--
-- -   #VUID-VkCopyMicromapToMemoryInfoEXT-src-07540# The source micromap
--     @src@ /must/ have been constructed prior to the execution of this
--     command
--
-- -   #VUID-VkCopyMicromapToMemoryInfoEXT-dst-07541# The memory pointed to
--     by @dst@ /must/ be at least as large as the serialization size of
--     @src@, as reported by 'writeMicromapsPropertiesEXT' or
--     'cmdWriteMicromapsPropertiesEXT' with a query type of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_MICROMAP_SERIALIZATION_SIZE_EXT'
--
-- -   #VUID-VkCopyMicromapToMemoryInfoEXT-mode-07542# @mode@ /must/ be
--     'COPY_MICROMAP_MODE_SERIALIZE_EXT'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkCopyMicromapToMemoryInfoEXT-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COPY_MICROMAP_TO_MEMORY_INFO_EXT'
--
-- -   #VUID-VkCopyMicromapToMemoryInfoEXT-pNext-pNext# @pNext@ /must/ be
--     @NULL@
--
-- -   #VUID-VkCopyMicromapToMemoryInfoEXT-src-parameter# @src@ /must/ be a
--     valid 'Vulkan.Extensions.Handles.MicromapEXT' handle
--
-- -   #VUID-VkCopyMicromapToMemoryInfoEXT-mode-parameter# @mode@ /must/ be
--     a valid 'CopyMicromapModeEXT' value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'CopyMicromapModeEXT',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.DeviceOrHostAddressKHR',
-- 'Vulkan.Extensions.Handles.MicromapEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdCopyMicromapToMemoryEXT', 'copyMicromapToMemoryEXT'
data CopyMicromapToMemoryInfoEXT = CopyMicromapToMemoryInfoEXT
  { -- | @src@ is the source micromap for the copy
    CopyMicromapToMemoryInfoEXT -> MicromapEXT
src :: MicromapEXT
  , -- | @dst@ is the device or host address to memory which is the target for
    -- the copy
    CopyMicromapToMemoryInfoEXT -> DeviceOrHostAddressKHR
dst :: DeviceOrHostAddressKHR
  , -- | @mode@ is a 'CopyMicromapModeEXT' value specifying additional operations
    -- to perform during the copy.
    CopyMicromapToMemoryInfoEXT -> CopyMicromapModeEXT
mode :: CopyMicromapModeEXT
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CopyMicromapToMemoryInfoEXT)
#endif
deriving instance Show CopyMicromapToMemoryInfoEXT

instance ToCStruct CopyMicromapToMemoryInfoEXT where
  withCStruct :: forall b.
CopyMicromapToMemoryInfoEXT
-> (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO b) -> IO b
withCStruct CopyMicromapToMemoryInfoEXT
x ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO b
f = Int
-> (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO b) -> IO b)
-> (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \"pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p -> ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> CopyMicromapToMemoryInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p CopyMicromapToMemoryInfoEXT
x (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO b
f "pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p)
  pokeCStruct :: forall b.
("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> CopyMicromapToMemoryInfoEXT -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p CopyMicromapToMemoryInfoEXT{MicromapEXT
DeviceOrHostAddressKHR
CopyMicromapModeEXT
mode :: CopyMicromapModeEXT
dst :: DeviceOrHostAddressKHR
src :: MicromapEXT
$sel:mode:CopyMicromapToMemoryInfoEXT :: CopyMicromapToMemoryInfoEXT -> CopyMicromapModeEXT
$sel:dst:CopyMicromapToMemoryInfoEXT :: CopyMicromapToMemoryInfoEXT -> DeviceOrHostAddressKHR
$sel:src:CopyMicromapToMemoryInfoEXT :: CopyMicromapToMemoryInfoEXT -> MicromapEXT
..} IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_MICROMAP_TO_MEMORY_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MicromapEXT)) (MicromapEXT
src)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressKHR
-> DeviceOrHostAddressKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> Ptr DeviceOrHostAddressKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceOrHostAddressKHR)) (DeviceOrHostAddressKHR
dst) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> Ptr CopyMicromapModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CopyMicromapModeEXT)) (CopyMicromapModeEXT
mode)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_MICROMAP_TO_MEMORY_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr MicromapEXT)) (MicromapEXT
forall a. Zero a => a
zero)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressKHR
-> DeviceOrHostAddressKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> Ptr DeviceOrHostAddressKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceOrHostAddressKHR)) (DeviceOrHostAddressKHR
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT
p ("pInfo" ::: Ptr CopyMicromapToMemoryInfoEXT)
-> Int -> Ptr CopyMicromapModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CopyMicromapModeEXT)) (CopyMicromapModeEXT
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance Zero CopyMicromapToMemoryInfoEXT where
  zero :: CopyMicromapToMemoryInfoEXT
zero = MicromapEXT
-> DeviceOrHostAddressKHR
-> CopyMicromapModeEXT
-> CopyMicromapToMemoryInfoEXT
CopyMicromapToMemoryInfoEXT
           MicromapEXT
forall a. Zero a => a
zero
           DeviceOrHostAddressKHR
forall a. Zero a => a
zero
           CopyMicromapModeEXT
forall a. Zero a => a
zero


-- | VkCopyMemoryToMicromapInfoEXT - Parameters for deserializing a micromap
--
-- == Valid Usage
--
-- -   #VUID-VkCopyMemoryToMicromapInfoEXT-src-07547# The source memory
--     pointed to by @src@ /must/ contain data previously serialized using
--     'cmdCopyMicromapToMemoryEXT'
--
-- -   #VUID-VkCopyMemoryToMicromapInfoEXT-mode-07548# @mode@ /must/ be
--     'COPY_MICROMAP_MODE_DESERIALIZE_EXT'
--
-- -   #VUID-VkCopyMemoryToMicromapInfoEXT-src-07549# The data in @src@
--     /must/ have a format compatible with the destination physical device
--     as returned by 'getDeviceMicromapCompatibilityEXT'
--
-- -   #VUID-VkCopyMemoryToMicromapInfoEXT-dst-07550# @dst@ /must/ have
--     been created with a @size@ greater than or equal to that used to
--     serialize the data in @src@
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkCopyMemoryToMicromapInfoEXT-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COPY_MEMORY_TO_MICROMAP_INFO_EXT'
--
-- -   #VUID-VkCopyMemoryToMicromapInfoEXT-pNext-pNext# @pNext@ /must/ be
--     @NULL@
--
-- -   #VUID-VkCopyMemoryToMicromapInfoEXT-dst-parameter# @dst@ /must/ be a
--     valid 'Vulkan.Extensions.Handles.MicromapEXT' handle
--
-- -   #VUID-VkCopyMemoryToMicromapInfoEXT-mode-parameter# @mode@ /must/ be
--     a valid 'CopyMicromapModeEXT' value
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'CopyMicromapModeEXT',
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.DeviceOrHostAddressConstKHR',
-- 'Vulkan.Extensions.Handles.MicromapEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdCopyMemoryToMicromapEXT', 'copyMemoryToMicromapEXT'
data CopyMemoryToMicromapInfoEXT = CopyMemoryToMicromapInfoEXT
  { -- | @src@ is the device or host address to memory containing the source data
    -- for the copy.
    CopyMemoryToMicromapInfoEXT -> DeviceOrHostAddressConstKHR
src :: DeviceOrHostAddressConstKHR
  , -- | @dst@ is the target micromap for the copy.
    CopyMemoryToMicromapInfoEXT -> MicromapEXT
dst :: MicromapEXT
  , -- | @mode@ is a 'CopyMicromapModeEXT' value specifying additional operations
    -- to perform during the copy.
    CopyMemoryToMicromapInfoEXT -> CopyMicromapModeEXT
mode :: CopyMicromapModeEXT
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CopyMemoryToMicromapInfoEXT)
#endif
deriving instance Show CopyMemoryToMicromapInfoEXT

instance ToCStruct CopyMemoryToMicromapInfoEXT where
  withCStruct :: forall b.
CopyMemoryToMicromapInfoEXT
-> (Ptr CopyMemoryToMicromapInfoEXT -> IO b) -> IO b
withCStruct CopyMemoryToMicromapInfoEXT
x Ptr CopyMemoryToMicromapInfoEXT -> IO b
f = Int -> (Ptr CopyMemoryToMicromapInfoEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((Ptr CopyMemoryToMicromapInfoEXT -> IO b) -> IO b)
-> (Ptr CopyMemoryToMicromapInfoEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr CopyMemoryToMicromapInfoEXT
p -> Ptr CopyMemoryToMicromapInfoEXT
-> CopyMemoryToMicromapInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr CopyMemoryToMicromapInfoEXT
p CopyMemoryToMicromapInfoEXT
x (Ptr CopyMemoryToMicromapInfoEXT -> IO b
f Ptr CopyMemoryToMicromapInfoEXT
p)
  pokeCStruct :: forall b.
Ptr CopyMemoryToMicromapInfoEXT
-> CopyMemoryToMicromapInfoEXT -> IO b -> IO b
pokeCStruct Ptr CopyMemoryToMicromapInfoEXT
p CopyMemoryToMicromapInfoEXT{MicromapEXT
DeviceOrHostAddressConstKHR
CopyMicromapModeEXT
mode :: CopyMicromapModeEXT
dst :: MicromapEXT
src :: DeviceOrHostAddressConstKHR
$sel:mode:CopyMemoryToMicromapInfoEXT :: CopyMemoryToMicromapInfoEXT -> CopyMicromapModeEXT
$sel:dst:CopyMemoryToMicromapInfoEXT :: CopyMemoryToMicromapInfoEXT -> MicromapEXT
$sel:src:CopyMemoryToMicromapInfoEXT :: CopyMemoryToMicromapInfoEXT -> DeviceOrHostAddressConstKHR
..} IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_MEMORY_TO_MICROMAP_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
src) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT
-> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr MicromapEXT)) (MicromapEXT
dst)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT -> Int -> Ptr CopyMicromapModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CopyMicromapModeEXT)) (CopyMicromapModeEXT
mode)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b. Ptr CopyMemoryToMicromapInfoEXT -> IO b -> IO b
pokeZeroCStruct Ptr CopyMemoryToMicromapInfoEXT
p IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_MEMORY_TO_MICROMAP_INFO_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT -> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT
-> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr MicromapEXT)) (MicromapEXT
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr CopyMemoryToMicromapInfoEXT
p Ptr CopyMemoryToMicromapInfoEXT -> Int -> Ptr CopyMicromapModeEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr CopyMicromapModeEXT)) (CopyMicromapModeEXT
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance Zero CopyMemoryToMicromapInfoEXT where
  zero :: CopyMemoryToMicromapInfoEXT
zero = DeviceOrHostAddressConstKHR
-> MicromapEXT
-> CopyMicromapModeEXT
-> CopyMemoryToMicromapInfoEXT
CopyMemoryToMicromapInfoEXT
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero
           MicromapEXT
forall a. Zero a => a
zero
           CopyMicromapModeEXT
forall a. Zero a => a
zero


-- | VkMicromapBuildSizesInfoEXT - Structure specifying build sizes for a
-- micromap
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getMicromapBuildSizesEXT'
data MicromapBuildSizesInfoEXT = MicromapBuildSizesInfoEXT
  { -- | @micromapSize@ is the size in bytes required in a
    -- 'Vulkan.Extensions.Handles.MicromapEXT' for a build or update operation.
    MicromapBuildSizesInfoEXT -> "dataSize" ::: Word64
micromapSize :: DeviceSize
  , -- | @buildScratchSize@ is the size in bytes required in a scratch buffer for
    -- a build operation.
    MicromapBuildSizesInfoEXT -> "dataSize" ::: Word64
buildScratchSize :: DeviceSize
  , -- | @discardable@ indicates whether or not the micromap object may be
    -- destroyed after an acceleration structure build or update. A false value
    -- means that acceleration structures built with this micromap /may/
    -- contain references to the data contained therein, and the application
    -- /must/ not destroy the micromap until ray traversal has concluded. A
    -- true value means that the information in the micromap will be copied by
    -- value into the acceleration structure, and the micromap /may/ be
    -- destroyed after the acceleration structure build concludes.
    MicromapBuildSizesInfoEXT -> Bool
discardable :: Bool
  }
  deriving (Typeable, MicromapBuildSizesInfoEXT -> MicromapBuildSizesInfoEXT -> Bool
(MicromapBuildSizesInfoEXT -> MicromapBuildSizesInfoEXT -> Bool)
-> (MicromapBuildSizesInfoEXT -> MicromapBuildSizesInfoEXT -> Bool)
-> Eq MicromapBuildSizesInfoEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MicromapBuildSizesInfoEXT -> MicromapBuildSizesInfoEXT -> Bool
$c/= :: MicromapBuildSizesInfoEXT -> MicromapBuildSizesInfoEXT -> Bool
== :: MicromapBuildSizesInfoEXT -> MicromapBuildSizesInfoEXT -> Bool
$c== :: MicromapBuildSizesInfoEXT -> MicromapBuildSizesInfoEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MicromapBuildSizesInfoEXT)
#endif
deriving instance Show MicromapBuildSizesInfoEXT

instance ToCStruct MicromapBuildSizesInfoEXT where
  withCStruct :: forall b.
MicromapBuildSizesInfoEXT
-> (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT) -> IO b)
-> IO b
withCStruct MicromapBuildSizesInfoEXT
x ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT) -> IO b
f = Int
-> (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT) -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT) -> IO b) -> IO b)
-> (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \"pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p -> ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> MicromapBuildSizesInfoEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p MicromapBuildSizesInfoEXT
x (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT) -> IO b
f "pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p)
  pokeCStruct :: forall b.
("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> MicromapBuildSizesInfoEXT -> IO b -> IO b
pokeCStruct "pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p MicromapBuildSizesInfoEXT{Bool
"dataSize" ::: Word64
discardable :: Bool
buildScratchSize :: "dataSize" ::: Word64
micromapSize :: "dataSize" ::: Word64
$sel:discardable:MicromapBuildSizesInfoEXT :: MicromapBuildSizesInfoEXT -> Bool
$sel:buildScratchSize:MicromapBuildSizesInfoEXT :: MicromapBuildSizesInfoEXT -> "dataSize" ::: Word64
$sel:micromapSize:MicromapBuildSizesInfoEXT :: MicromapBuildSizesInfoEXT -> "dataSize" ::: Word64
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MICROMAP_BUILD_SIZES_INFO_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) ("dataSize" ::: Word64
micromapSize)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) ("dataSize" ::: Word64
buildScratchSize)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
discardable))
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT) -> IO b -> IO b
pokeZeroCStruct "pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MICROMAP_BUILD_SIZES_INFO_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct MicromapBuildSizesInfoEXT where
  peekCStruct :: ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> IO MicromapBuildSizesInfoEXT
peekCStruct "pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p = do
    "dataSize" ::: Word64
micromapSize <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr DeviceSize))
    "dataSize" ::: Word64
buildScratchSize <- forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceSize))
    Bool32
discardable <- forall a. Storable a => Ptr a -> IO a
peek @Bool32 (("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT
p ("pSizeInfo" ::: Ptr MicromapBuildSizesInfoEXT)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr Bool32))
    MicromapBuildSizesInfoEXT -> IO MicromapBuildSizesInfoEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MicromapBuildSizesInfoEXT -> IO MicromapBuildSizesInfoEXT)
-> MicromapBuildSizesInfoEXT -> IO MicromapBuildSizesInfoEXT
forall a b. (a -> b) -> a -> b
$ ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64) -> Bool -> MicromapBuildSizesInfoEXT
MicromapBuildSizesInfoEXT
             "dataSize" ::: Word64
micromapSize "dataSize" ::: Word64
buildScratchSize (Bool32 -> Bool
bool32ToBool Bool32
discardable)

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

instance Zero MicromapBuildSizesInfoEXT where
  zero :: MicromapBuildSizesInfoEXT
zero = ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64) -> Bool -> MicromapBuildSizesInfoEXT
MicromapBuildSizesInfoEXT
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkMicromapUsageEXT - Structure specifying the usage information used to
-- build a micromap
--
-- == Valid Usage
--
-- -   #VUID-VkMicromapUsageEXT-format-07519# If the 'MicromapTypeEXT' of
--     the micromap is 'MICROMAP_TYPE_OPACITY_MICROMAP_EXT' then @format@
--     /must/ be 'OPACITY_MICROMAP_FORMAT_2_STATE_EXT' or
--     'OPACITY_MICROMAP_FORMAT_4_STATE_EXT'.
--
-- -   #VUID-VkMicromapUsageEXT-format-07520# If the 'MicromapTypeEXT' of
--     the micromap is 'MICROMAP_TYPE_OPACITY_MICROMAP_EXT' and @format@ is
--     'OPACITY_MICROMAP_FORMAT_2_STATE_EXT' then @subdivisionLevel@ /must/
--     be less than or equal to @maxOpacity2StateSubdivisionLevel@ of
--     'PhysicalDeviceOpacityMicromapPropertiesEXT'
--
-- -   #VUID-VkMicromapUsageEXT-format-07521# If the 'MicromapTypeEXT' of
--     the micromap is 'MICROMAP_TYPE_OPACITY_MICROMAP_EXT' and @format@ is
--     'OPACITY_MICROMAP_FORMAT_4_STATE_EXT' then @subdivisionLevel@ /must/
--     be less than or equal to @maxOpacity4StateSubdivisionLevel@ of
--     'PhysicalDeviceOpacityMicromapPropertiesEXT'
--
-- The @format@ is interpreted based on the @type@ of the micromap using
-- it.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'AccelerationStructureTrianglesOpacityMicromapEXT',
-- 'MicromapBuildInfoEXT'
data MicromapUsageEXT = MicromapUsageEXT
  { -- | @count@ is the number of triangles in the usage format defined by the
    -- @subdivisionLevel@ and @format@ below in the micromap
    MicromapUsageEXT -> Flags
count :: Word32
  , -- | @subdivisionLevel@ is the subdivision level of this usage format
    MicromapUsageEXT -> Flags
subdivisionLevel :: Word32
  , -- | @format@ is the format of this usage format
    MicromapUsageEXT -> Flags
format :: Word32
  }
  deriving (Typeable, MicromapUsageEXT -> MicromapUsageEXT -> Bool
(MicromapUsageEXT -> MicromapUsageEXT -> Bool)
-> (MicromapUsageEXT -> MicromapUsageEXT -> Bool)
-> Eq MicromapUsageEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MicromapUsageEXT -> MicromapUsageEXT -> Bool
$c/= :: MicromapUsageEXT -> MicromapUsageEXT -> Bool
== :: MicromapUsageEXT -> MicromapUsageEXT -> Bool
$c== :: MicromapUsageEXT -> MicromapUsageEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MicromapUsageEXT)
#endif
deriving instance Show MicromapUsageEXT

instance ToCStruct MicromapUsageEXT where
  withCStruct :: forall b.
MicromapUsageEXT -> (Ptr MicromapUsageEXT -> IO b) -> IO b
withCStruct MicromapUsageEXT
x Ptr MicromapUsageEXT -> IO b
f = Int -> (Ptr MicromapUsageEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
12 ((Ptr MicromapUsageEXT -> IO b) -> IO b)
-> (Ptr MicromapUsageEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr MicromapUsageEXT
p -> Ptr MicromapUsageEXT -> MicromapUsageEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MicromapUsageEXT
p MicromapUsageEXT
x (Ptr MicromapUsageEXT -> IO b
f Ptr MicromapUsageEXT
p)
  pokeCStruct :: forall b. Ptr MicromapUsageEXT -> MicromapUsageEXT -> IO b -> IO b
pokeCStruct Ptr MicromapUsageEXT
p MicromapUsageEXT{Flags
format :: Flags
subdivisionLevel :: Flags
count :: Flags
$sel:format:MicromapUsageEXT :: MicromapUsageEXT -> Flags
$sel:subdivisionLevel:MicromapUsageEXT :: MicromapUsageEXT -> Flags
$sel:count:MicromapUsageEXT :: MicromapUsageEXT -> Flags
..} IO b
f = do
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapUsageEXT
p Ptr MicromapUsageEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Flags
count)
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapUsageEXT
p Ptr MicromapUsageEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Flags
subdivisionLevel)
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapUsageEXT
p Ptr MicromapUsageEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Flags
format)
    IO b
f
  cStructSize :: Int
cStructSize = Int
12
  cStructAlignment :: Int
cStructAlignment = Int
4
  pokeZeroCStruct :: forall b. Ptr MicromapUsageEXT -> IO b -> IO b
pokeZeroCStruct Ptr MicromapUsageEXT
p IO b
f = do
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapUsageEXT
p Ptr MicromapUsageEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Flags
forall a. Zero a => a
zero)
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapUsageEXT
p Ptr MicromapUsageEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32)) (Flags
forall a. Zero a => a
zero)
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapUsageEXT
p Ptr MicromapUsageEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32)) (Flags
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct MicromapUsageEXT where
  peekCStruct :: Ptr MicromapUsageEXT -> IO MicromapUsageEXT
peekCStruct Ptr MicromapUsageEXT
p = do
    Flags
count <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr MicromapUsageEXT
p Ptr MicromapUsageEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
    Flags
subdivisionLevel <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr MicromapUsageEXT
p Ptr MicromapUsageEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word32))
    Flags
format <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr MicromapUsageEXT
p Ptr MicromapUsageEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr Word32))
    MicromapUsageEXT -> IO MicromapUsageEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MicromapUsageEXT -> IO MicromapUsageEXT)
-> MicromapUsageEXT -> IO MicromapUsageEXT
forall a b. (a -> b) -> a -> b
$ Flags -> Flags -> Flags -> MicromapUsageEXT
MicromapUsageEXT
             Flags
count Flags
subdivisionLevel Flags
format

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

instance Zero MicromapUsageEXT where
  zero :: MicromapUsageEXT
zero = Flags -> Flags -> Flags -> MicromapUsageEXT
MicromapUsageEXT
           Flags
forall a. Zero a => a
zero
           Flags
forall a. Zero a => a
zero
           Flags
forall a. Zero a => a
zero


-- | VkMicromapTriangleEXT - Structure specifying the micromap format and
-- data for a triangle
--
-- == Valid Usage
--
-- -   #VUID-VkMicromapTriangleEXT-format-07522# If the 'MicromapTypeEXT'
--     of the micromap is 'MICROMAP_TYPE_OPACITY_MICROMAP_EXT' then
--     @format@ /must/ be 'OPACITY_MICROMAP_FORMAT_2_STATE_EXT' or
--     'OPACITY_MICROMAP_FORMAT_4_STATE_EXT'.
--
-- -   #VUID-VkMicromapTriangleEXT-format-07523# If the 'MicromapTypeEXT'
--     of the micromap is 'MICROMAP_TYPE_OPACITY_MICROMAP_EXT' and @format@
--     is 'OPACITY_MICROMAP_FORMAT_2_STATE_EXT' then @subdivisionLevel@
--     /must/ be less than or equal to @maxOpacity2StateSubdivisionLevel@
--     of 'PhysicalDeviceOpacityMicromapPropertiesEXT'
--
-- -   #VUID-VkMicromapTriangleEXT-format-07524# If the 'MicromapTypeEXT'
--     of the micromap is 'MICROMAP_TYPE_OPACITY_MICROMAP_EXT' and @format@
--     is 'OPACITY_MICROMAP_FORMAT_4_STATE_EXT' then @subdivisionLevel@
--     /must/ be less than or equal to @maxOpacity4StateSubdivisionLevel@
--     of 'PhysicalDeviceOpacityMicromapPropertiesEXT'
--
-- The @format@ is interpreted based on the @type@ of the micromap using
-- it.
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>
data MicromapTriangleEXT = MicromapTriangleEXT
  { -- | @dataOffset@ is the offset in bytes of the start of the data for this
    -- triangle. This is a byte aligned value.
    MicromapTriangleEXT -> Flags
dataOffset :: Word32
  , -- | @subdivisionLevel@ is the subdivision level of this triangle
    MicromapTriangleEXT -> Word16
subdivisionLevel :: Word16
  , -- | @format@ is the format of this triangle
    MicromapTriangleEXT -> Word16
format :: Word16
  }
  deriving (Typeable, MicromapTriangleEXT -> MicromapTriangleEXT -> Bool
(MicromapTriangleEXT -> MicromapTriangleEXT -> Bool)
-> (MicromapTriangleEXT -> MicromapTriangleEXT -> Bool)
-> Eq MicromapTriangleEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MicromapTriangleEXT -> MicromapTriangleEXT -> Bool
$c/= :: MicromapTriangleEXT -> MicromapTriangleEXT -> Bool
== :: MicromapTriangleEXT -> MicromapTriangleEXT -> Bool
$c== :: MicromapTriangleEXT -> MicromapTriangleEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (MicromapTriangleEXT)
#endif
deriving instance Show MicromapTriangleEXT

instance ToCStruct MicromapTriangleEXT where
  withCStruct :: forall b.
MicromapTriangleEXT -> (Ptr MicromapTriangleEXT -> IO b) -> IO b
withCStruct MicromapTriangleEXT
x Ptr MicromapTriangleEXT -> IO b
f = Int -> (Ptr MicromapTriangleEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
8 ((Ptr MicromapTriangleEXT -> IO b) -> IO b)
-> (Ptr MicromapTriangleEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr MicromapTriangleEXT
p -> Ptr MicromapTriangleEXT -> MicromapTriangleEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr MicromapTriangleEXT
p MicromapTriangleEXT
x (Ptr MicromapTriangleEXT -> IO b
f Ptr MicromapTriangleEXT
p)
  pokeCStruct :: forall b.
Ptr MicromapTriangleEXT -> MicromapTriangleEXT -> IO b -> IO b
pokeCStruct Ptr MicromapTriangleEXT
p MicromapTriangleEXT{Word16
Flags
format :: Word16
subdivisionLevel :: Word16
dataOffset :: Flags
$sel:format:MicromapTriangleEXT :: MicromapTriangleEXT -> Word16
$sel:subdivisionLevel:MicromapTriangleEXT :: MicromapTriangleEXT -> Word16
$sel:dataOffset:MicromapTriangleEXT :: MicromapTriangleEXT -> Flags
..} IO b
f = do
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapTriangleEXT
p Ptr MicromapTriangleEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Flags
dataOffset)
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapTriangleEXT
p Ptr MicromapTriangleEXT -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word16)) (Word16
subdivisionLevel)
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapTriangleEXT
p Ptr MicromapTriangleEXT -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
6 :: Ptr Word16)) (Word16
format)
    IO b
f
  cStructSize :: Int
cStructSize = Int
8
  cStructAlignment :: Int
cStructAlignment = Int
4
  pokeZeroCStruct :: forall b. Ptr MicromapTriangleEXT -> IO b -> IO b
pokeZeroCStruct Ptr MicromapTriangleEXT
p IO b
f = do
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapTriangleEXT
p Ptr MicromapTriangleEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32)) (Flags
forall a. Zero a => a
zero)
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapTriangleEXT
p Ptr MicromapTriangleEXT -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word16)) (Word16
forall a. Zero a => a
zero)
    Ptr Word16 -> Word16 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr MicromapTriangleEXT
p Ptr MicromapTriangleEXT -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
6 :: Ptr Word16)) (Word16
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct MicromapTriangleEXT where
  peekCStruct :: Ptr MicromapTriangleEXT -> IO MicromapTriangleEXT
peekCStruct Ptr MicromapTriangleEXT
p = do
    Flags
dataOffset <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr MicromapTriangleEXT
p Ptr MicromapTriangleEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr Word32))
    Word16
subdivisionLevel <- forall a. Storable a => Ptr a -> IO a
peek @Word16 ((Ptr MicromapTriangleEXT
p Ptr MicromapTriangleEXT -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
4 :: Ptr Word16))
    Word16
format <- forall a. Storable a => Ptr a -> IO a
peek @Word16 ((Ptr MicromapTriangleEXT
p Ptr MicromapTriangleEXT -> Int -> Ptr Word16
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
6 :: Ptr Word16))
    MicromapTriangleEXT -> IO MicromapTriangleEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MicromapTriangleEXT -> IO MicromapTriangleEXT)
-> MicromapTriangleEXT -> IO MicromapTriangleEXT
forall a b. (a -> b) -> a -> b
$ Flags -> Word16 -> Word16 -> MicromapTriangleEXT
MicromapTriangleEXT
             Flags
dataOffset Word16
subdivisionLevel Word16
format

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

instance Zero MicromapTriangleEXT where
  zero :: MicromapTriangleEXT
zero = Flags -> Word16 -> Word16 -> MicromapTriangleEXT
MicromapTriangleEXT
           Flags
forall a. Zero a => a
zero
           Word16
forall a. Zero a => a
zero
           Word16
forall a. Zero a => a
zero


-- | VkPhysicalDeviceOpacityMicromapFeaturesEXT - Structure describing the
-- ray tracing opacity micromap features that can be supported by an
-- implementation
--
-- = Members
--
-- This structure describes the following feature:
--
-- = Description
--
-- If the 'PhysicalDeviceOpacityMicromapFeaturesEXT' 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. 'PhysicalDeviceOpacityMicromapFeaturesEXT' /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_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceOpacityMicromapFeaturesEXT = PhysicalDeviceOpacityMicromapFeaturesEXT
  { -- | #features-micromap# @micromap@ indicates whether the implementation
    -- supports the micromap array feature.
    PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
micromap :: Bool
  , -- | #features-micromapCaptureReplay# @micromapCaptureReplay@ indicates
    -- whether the implementation supports capture and replay of addresses for
    -- micromap arrays.
    PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
micromapCaptureReplay :: Bool
  , -- | #features-micromapHostCommands# @micromapHostCommands@ indicates whether
    -- the implementation supports host side micromap array commands.
    PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
micromapHostCommands :: Bool
  }
  deriving (Typeable, PhysicalDeviceOpacityMicromapFeaturesEXT
-> PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
(PhysicalDeviceOpacityMicromapFeaturesEXT
 -> PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool)
-> (PhysicalDeviceOpacityMicromapFeaturesEXT
    -> PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool)
-> Eq PhysicalDeviceOpacityMicromapFeaturesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceOpacityMicromapFeaturesEXT
-> PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
$c/= :: PhysicalDeviceOpacityMicromapFeaturesEXT
-> PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
== :: PhysicalDeviceOpacityMicromapFeaturesEXT
-> PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
$c== :: PhysicalDeviceOpacityMicromapFeaturesEXT
-> PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceOpacityMicromapFeaturesEXT)
#endif
deriving instance Show PhysicalDeviceOpacityMicromapFeaturesEXT

instance ToCStruct PhysicalDeviceOpacityMicromapFeaturesEXT where
  withCStruct :: forall b.
PhysicalDeviceOpacityMicromapFeaturesEXT
-> (Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceOpacityMicromapFeaturesEXT
x Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
32 ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p -> Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
-> PhysicalDeviceOpacityMicromapFeaturesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p PhysicalDeviceOpacityMicromapFeaturesEXT
x (Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> IO b
f Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
-> PhysicalDeviceOpacityMicromapFeaturesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p PhysicalDeviceOpacityMicromapFeaturesEXT{Bool
micromapHostCommands :: Bool
micromapCaptureReplay :: Bool
micromap :: Bool
$sel:micromapHostCommands:PhysicalDeviceOpacityMicromapFeaturesEXT :: PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
$sel:micromapCaptureReplay:PhysicalDeviceOpacityMicromapFeaturesEXT :: PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
$sel:micromap:PhysicalDeviceOpacityMicromapFeaturesEXT :: PhysicalDeviceOpacityMicromapFeaturesEXT -> Bool
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_OPACITY_MICROMAP_FEATURES_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
micromap))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
micromapCaptureReplay))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
micromapHostCommands))
    IO b
f
  cStructSize :: Int
cStructSize = Int
32
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_OPACITY_MICROMAP_FEATURES_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> 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))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapFeaturesEXT
p Ptr PhysicalDeviceOpacityMicromapFeaturesEXT -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

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

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

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


-- | VkPhysicalDeviceOpacityMicromapPropertiesEXT - Structure describing the
-- opacity micromap properties of a physical device
--
-- = Description
--
-- If the 'PhysicalDeviceOpacityMicromapPropertiesEXT' structure is
-- included in the @pNext@ chain of the
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2'
-- structure passed to
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceProperties2',
-- it is filled in with each corresponding implementation-dependent
-- property.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceOpacityMicromapPropertiesEXT = PhysicalDeviceOpacityMicromapPropertiesEXT
  { -- | @maxOpacity2StateSubdivisionLevel@ is the maximum allowed
    -- @subdivisionLevel@ when @format@ is
    -- 'OPACITY_MICROMAP_FORMAT_2_STATE_EXT'
    PhysicalDeviceOpacityMicromapPropertiesEXT -> Flags
maxOpacity2StateSubdivisionLevel :: Word32
  , -- | @maxOpacity4StateSubdivisionLevel@ is the maximum allowed
    -- @subdivisionLevel@ when @format@ is
    -- 'OPACITY_MICROMAP_FORMAT_4_STATE_EXT'
    PhysicalDeviceOpacityMicromapPropertiesEXT -> Flags
maxOpacity4StateSubdivisionLevel :: Word32
  }
  deriving (Typeable, PhysicalDeviceOpacityMicromapPropertiesEXT
-> PhysicalDeviceOpacityMicromapPropertiesEXT -> Bool
(PhysicalDeviceOpacityMicromapPropertiesEXT
 -> PhysicalDeviceOpacityMicromapPropertiesEXT -> Bool)
-> (PhysicalDeviceOpacityMicromapPropertiesEXT
    -> PhysicalDeviceOpacityMicromapPropertiesEXT -> Bool)
-> Eq PhysicalDeviceOpacityMicromapPropertiesEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceOpacityMicromapPropertiesEXT
-> PhysicalDeviceOpacityMicromapPropertiesEXT -> Bool
$c/= :: PhysicalDeviceOpacityMicromapPropertiesEXT
-> PhysicalDeviceOpacityMicromapPropertiesEXT -> Bool
== :: PhysicalDeviceOpacityMicromapPropertiesEXT
-> PhysicalDeviceOpacityMicromapPropertiesEXT -> Bool
$c== :: PhysicalDeviceOpacityMicromapPropertiesEXT
-> PhysicalDeviceOpacityMicromapPropertiesEXT -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceOpacityMicromapPropertiesEXT)
#endif
deriving instance Show PhysicalDeviceOpacityMicromapPropertiesEXT

instance ToCStruct PhysicalDeviceOpacityMicromapPropertiesEXT where
  withCStruct :: forall b.
PhysicalDeviceOpacityMicromapPropertiesEXT
-> (Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> IO b) -> IO b
withCStruct PhysicalDeviceOpacityMicromapPropertiesEXT
x Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> IO b
f = Int
-> (Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> IO b) -> IO b)
-> (Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p -> Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
-> PhysicalDeviceOpacityMicromapPropertiesEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p PhysicalDeviceOpacityMicromapPropertiesEXT
x (Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> IO b
f Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p)
  pokeCStruct :: forall b.
Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
-> PhysicalDeviceOpacityMicromapPropertiesEXT -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p PhysicalDeviceOpacityMicromapPropertiesEXT{Flags
maxOpacity4StateSubdivisionLevel :: Flags
maxOpacity2StateSubdivisionLevel :: Flags
$sel:maxOpacity4StateSubdivisionLevel:PhysicalDeviceOpacityMicromapPropertiesEXT :: PhysicalDeviceOpacityMicromapPropertiesEXT -> Flags
$sel:maxOpacity2StateSubdivisionLevel:PhysicalDeviceOpacityMicromapPropertiesEXT :: PhysicalDeviceOpacityMicromapPropertiesEXT -> Flags
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_OPACITY_MICROMAP_PROPERTIES_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Flags
maxOpacity2StateSubdivisionLevel)
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (Flags
maxOpacity4StateSubdivisionLevel)
    IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> IO b -> IO b
pokeZeroCStruct Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_OPACITY_MICROMAP_PROPERTIES_EXT)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32)) (Flags
forall a. Zero a => a
zero)
    Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32)) (Flags
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceOpacityMicromapPropertiesEXT where
  peekCStruct :: Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
-> IO PhysicalDeviceOpacityMicromapPropertiesEXT
peekCStruct Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p = do
    Flags
maxOpacity2StateSubdivisionLevel <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr Word32))
    Flags
maxOpacity4StateSubdivisionLevel <- forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceOpacityMicromapPropertiesEXT
p Ptr PhysicalDeviceOpacityMicromapPropertiesEXT -> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
20 :: Ptr Word32))
    PhysicalDeviceOpacityMicromapPropertiesEXT
-> IO PhysicalDeviceOpacityMicromapPropertiesEXT
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceOpacityMicromapPropertiesEXT
 -> IO PhysicalDeviceOpacityMicromapPropertiesEXT)
-> PhysicalDeviceOpacityMicromapPropertiesEXT
-> IO PhysicalDeviceOpacityMicromapPropertiesEXT
forall a b. (a -> b) -> a -> b
$ Flags -> Flags -> PhysicalDeviceOpacityMicromapPropertiesEXT
PhysicalDeviceOpacityMicromapPropertiesEXT
             Flags
maxOpacity2StateSubdivisionLevel Flags
maxOpacity4StateSubdivisionLevel

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

instance Zero PhysicalDeviceOpacityMicromapPropertiesEXT where
  zero :: PhysicalDeviceOpacityMicromapPropertiesEXT
zero = Flags -> Flags -> PhysicalDeviceOpacityMicromapPropertiesEXT
PhysicalDeviceOpacityMicromapPropertiesEXT
           Flags
forall a. Zero a => a
zero
           Flags
forall a. Zero a => a
zero


-- | VkAccelerationStructureTrianglesOpacityMicromapEXT - Structure
-- specifying an opacity micromap in a bottom-level acceleration structure
--
-- = Description
--
-- If 'AccelerationStructureTrianglesOpacityMicromapEXT' is included in the
-- @pNext@ chain of a
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.AccelerationStructureGeometryTrianglesDataKHR'
-- structure, that geometry will reference that micromap.
--
-- For each triangle in the geometry, the acceleration structure build
-- fetches an index from @indexBuffer@ using @indexType@ and @indexStride@.
-- If that value is the unsigned cast of one of the values from
-- 'OpacityMicromapSpecialIndexEXT' then that triangle behaves as described
-- for that special value in
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#ray-opacity-micromap Ray Opacity Micromap>.
-- Otherwise that triangle uses the opacity micromap information from
-- @micromap@ at that index plus @baseTriangle@.
--
-- Only one of @pUsageCounts@ or @ppUsageCounts@ /can/ be a valid pointer,
-- the other /must/ be @NULL@. The elements of the non-@NULL@ array
-- describe the total count used to build this geometry. For a given
-- @format@ and @subdivisionLevel@ the number of triangles in this geometry
-- matching those values after indirection and special index handling
-- /must/ be equal to the sum of matching @count@ provided.
--
-- If @micromap@ is 'Vulkan.Core10.APIConstants.NULL_HANDLE', then every
-- value read from @indexBuffer@ /must/ be one of the values in
-- 'OpacityMicromapSpecialIndexEXT'.
--
-- == Valid Usage
--
-- -   #VUID-VkAccelerationStructureTrianglesOpacityMicromapEXT-pUsageCounts-07335#
--     Only one of @pUsageCounts@ or @ppUsageCounts@ /can/ be a valid
--     pointer, the other /must/ be @NULL@.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkAccelerationStructureTrianglesOpacityMicromapEXT-sType-sType#
--     @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ACCELERATION_STRUCTURE_TRIANGLES_OPACITY_MICROMAP_EXT'
--
-- -   #VUID-VkAccelerationStructureTrianglesOpacityMicromapEXT-indexType-parameter#
--     @indexType@ /must/ be a valid
--     'Vulkan.Core10.Enums.IndexType.IndexType' value
--
-- -   #VUID-VkAccelerationStructureTrianglesOpacityMicromapEXT-pUsageCounts-parameter#
--     If @usageCountsCount@ is not @0@, and @pUsageCounts@ is not @NULL@,
--     @pUsageCounts@ /must/ be a valid pointer to an array of
--     @usageCountsCount@ 'MicromapUsageEXT' structures
--
-- -   #VUID-VkAccelerationStructureTrianglesOpacityMicromapEXT-ppUsageCounts-parameter#
--     If @usageCountsCount@ is not @0@, and @ppUsageCounts@ is not @NULL@,
--     @ppUsageCounts@ /must/ be a valid pointer to an array of
--     @usageCountsCount@ valid pointers to 'MicromapUsageEXT' structures
--
-- -   #VUID-VkAccelerationStructureTrianglesOpacityMicromapEXT-micromap-parameter#
--     @micromap@ /must/ be a valid 'Vulkan.Extensions.Handles.MicromapEXT'
--     handle
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'Vulkan.Extensions.VK_KHR_acceleration_structure.DeviceOrHostAddressConstKHR',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.IndexType.IndexType',
-- 'Vulkan.Extensions.Handles.MicromapEXT', 'MicromapUsageEXT',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AccelerationStructureTrianglesOpacityMicromapEXT = AccelerationStructureTrianglesOpacityMicromapEXT
  { -- | @indexType@ is the type of triangle indices used when indexing this
    -- micromap
    AccelerationStructureTrianglesOpacityMicromapEXT -> IndexType
indexType :: IndexType
  , -- | @indexBuffer@ is the address containing the triangle indices
    AccelerationStructureTrianglesOpacityMicromapEXT
-> DeviceOrHostAddressConstKHR
indexBuffer :: DeviceOrHostAddressConstKHR
  , -- | @indexStride@ is the byte stride between triangle indices
    AccelerationStructureTrianglesOpacityMicromapEXT
-> "dataSize" ::: Word64
indexStride :: DeviceSize
  , -- | @baseTriangle@ is the base value added to the non-negative triangle
    -- indices
    AccelerationStructureTrianglesOpacityMicromapEXT -> Flags
baseTriangle :: Word32
  , -- | @usageCountsCount@ specifies the number of usage counts structures that
    -- will be used to determine the size of this micromap.
    AccelerationStructureTrianglesOpacityMicromapEXT -> Flags
usageCountsCount :: Word32
  , -- | @pUsageCounts@ is a pointer to an array of 'MicromapUsageEXT'
    -- structures.
    AccelerationStructureTrianglesOpacityMicromapEXT
-> Vector MicromapUsageEXT
usageCounts :: Vector MicromapUsageEXT
  , -- | @micromap@ is the handle to the micromap object to include in this
    -- geometry
    AccelerationStructureTrianglesOpacityMicromapEXT -> MicromapEXT
micromap :: MicromapEXT
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureTrianglesOpacityMicromapEXT)
#endif
deriving instance Show AccelerationStructureTrianglesOpacityMicromapEXT

instance ToCStruct AccelerationStructureTrianglesOpacityMicromapEXT where
  withCStruct :: forall b.
AccelerationStructureTrianglesOpacityMicromapEXT
-> (Ptr AccelerationStructureTrianglesOpacityMicromapEXT -> IO b)
-> IO b
withCStruct AccelerationStructureTrianglesOpacityMicromapEXT
x Ptr AccelerationStructureTrianglesOpacityMicromapEXT -> IO b
f = Int
-> (Ptr AccelerationStructureTrianglesOpacityMicromapEXT -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
72 ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT -> IO b)
 -> IO b)
-> (Ptr AccelerationStructureTrianglesOpacityMicromapEXT -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p -> Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> AccelerationStructureTrianglesOpacityMicromapEXT -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p AccelerationStructureTrianglesOpacityMicromapEXT
x (Ptr AccelerationStructureTrianglesOpacityMicromapEXT -> IO b
f Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p)
  pokeCStruct :: forall b.
Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> AccelerationStructureTrianglesOpacityMicromapEXT -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p AccelerationStructureTrianglesOpacityMicromapEXT{Flags
"dataSize" ::: Word64
Vector MicromapUsageEXT
IndexType
MicromapEXT
DeviceOrHostAddressConstKHR
micromap :: MicromapEXT
usageCounts :: Vector MicromapUsageEXT
usageCountsCount :: Flags
baseTriangle :: Flags
indexStride :: "dataSize" ::: Word64
indexBuffer :: DeviceOrHostAddressConstKHR
indexType :: IndexType
$sel:micromap:AccelerationStructureTrianglesOpacityMicromapEXT :: AccelerationStructureTrianglesOpacityMicromapEXT -> MicromapEXT
$sel:usageCounts:AccelerationStructureTrianglesOpacityMicromapEXT :: AccelerationStructureTrianglesOpacityMicromapEXT
-> Vector MicromapUsageEXT
$sel:usageCountsCount:AccelerationStructureTrianglesOpacityMicromapEXT :: AccelerationStructureTrianglesOpacityMicromapEXT -> Flags
$sel:baseTriangle:AccelerationStructureTrianglesOpacityMicromapEXT :: AccelerationStructureTrianglesOpacityMicromapEXT -> Flags
$sel:indexStride:AccelerationStructureTrianglesOpacityMicromapEXT :: AccelerationStructureTrianglesOpacityMicromapEXT
-> "dataSize" ::: Word64
$sel:indexBuffer:AccelerationStructureTrianglesOpacityMicromapEXT :: AccelerationStructureTrianglesOpacityMicromapEXT
-> DeviceOrHostAddressConstKHR
$sel:indexType:AccelerationStructureTrianglesOpacityMicromapEXT :: AccelerationStructureTrianglesOpacityMicromapEXT -> IndexType
..} IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_TRIANGLES_OPACITY_MICROMAP_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr IndexType -> IndexType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr IndexType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr IndexType)) (IndexType
indexType)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
indexBuffer) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) ("dataSize" ::: Word64
indexStride)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word32)) (Flags
baseTriangle)
    let pUsageCountsLength :: Int
pUsageCountsLength = Vector MicromapUsageEXT -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector MicromapUsageEXT -> Int) -> Vector MicromapUsageEXT -> Int
forall a b. (a -> b) -> a -> b
$ (Vector MicromapUsageEXT
usageCounts)
    Flags
usageCountsCount'' <- IO Flags -> ContT b IO Flags
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Flags -> ContT b IO Flags) -> IO Flags -> ContT b IO Flags
forall a b. (a -> b) -> a -> b
$ if (Flags
usageCountsCount) Flags -> Flags -> Bool
forall a. Eq a => a -> a -> Bool
== Flags
0
      then Flags -> IO Flags
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags -> IO Flags) -> Flags -> IO Flags
forall a b. (a -> b) -> a -> b
$ Int -> Flags
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pUsageCountsLength
      else do
        Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int -> Flags
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pUsageCountsLength Flags -> Flags -> Bool
forall a. Eq a => a -> a -> Bool
== (Flags
usageCountsCount) Bool -> Bool -> Bool
|| Int
pUsageCountsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) (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 String
"" String
"pUsageCounts must be empty or have 'usageCountsCount' elements" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
        Flags -> IO Flags
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Flags
usageCountsCount)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
44 :: Ptr Word32)) (Flags
usageCountsCount'')
    Ptr MicromapUsageEXT
pUsageCounts'' <- if Vector MicromapUsageEXT -> Bool
forall a. Vector a -> Bool
Data.Vector.null (Vector MicromapUsageEXT
usageCounts)
      then Ptr MicromapUsageEXT -> ContT b IO (Ptr MicromapUsageEXT)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr MicromapUsageEXT
forall a. Ptr a
nullPtr
      else do
        Ptr MicromapUsageEXT
pPUsageCounts <- ((Ptr MicromapUsageEXT -> IO b) -> IO b)
-> ContT b IO (Ptr MicromapUsageEXT)
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr MicromapUsageEXT -> IO b) -> IO b)
 -> ContT b IO (Ptr MicromapUsageEXT))
-> ((Ptr MicromapUsageEXT -> IO b) -> IO b)
-> ContT b IO (Ptr MicromapUsageEXT)
forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @MicromapUsageEXT (((Vector MicromapUsageEXT -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector MicromapUsageEXT
usageCounts))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
12)
        IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> MicromapUsageEXT -> IO ())
-> Vector MicromapUsageEXT -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i MicromapUsageEXT
e -> Ptr MicromapUsageEXT -> MicromapUsageEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr MicromapUsageEXT
pPUsageCounts Ptr MicromapUsageEXT -> Int -> Ptr MicromapUsageEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
12 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MicromapUsageEXT) (MicromapUsageEXT
e)) ((Vector MicromapUsageEXT
usageCounts))
        Ptr MicromapUsageEXT -> ContT b IO (Ptr MicromapUsageEXT)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr MicromapUsageEXT -> ContT b IO (Ptr MicromapUsageEXT))
-> Ptr MicromapUsageEXT -> ContT b IO (Ptr MicromapUsageEXT)
forall a b. (a -> b) -> a -> b
$ Ptr MicromapUsageEXT
pPUsageCounts
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr MicromapUsageEXT) -> Ptr MicromapUsageEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr (Ptr MicromapUsageEXT)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
48 :: Ptr (Ptr MicromapUsageEXT))) Ptr MicromapUsageEXT
pUsageCounts''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (Ptr MicromapUsageEXT))
-> Ptr (Ptr MicromapUsageEXT) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr (Ptr (Ptr MicromapUsageEXT))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr (Ptr (Ptr MicromapUsageEXT)))) (Ptr (Ptr MicromapUsageEXT)
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr MicromapEXT)) (MicromapEXT
micromap)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
72
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: forall b.
Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> IO b -> IO b
pokeZeroCStruct Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_TRIANGLES_OPACITY_MICROMAP_EXT)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr IndexType -> IndexType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr IndexType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr IndexType)) (IndexType
forall a. Zero a => a
zero)
    ((() -> IO b) -> IO b) -> ContT b IO ()
forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO b) -> IO b) -> ContT b IO ())
-> ((() -> IO b) -> IO b) -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero) (IO b -> IO b) -> ((() -> IO b) -> IO b) -> (() -> IO b) -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO b) -> () -> IO b
forall a b. (a -> b) -> a -> b
$ ())
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr DeviceSize)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Flags -> Flags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr Flags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40 :: Ptr Word32)) (Flags
forall a. Zero a => a
zero)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr (Ptr MicromapUsageEXT))
-> Ptr (Ptr MicromapUsageEXT) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> Ptr (Ptr (Ptr MicromapUsageEXT))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
56 :: Ptr (Ptr (Ptr MicromapUsageEXT)))) (Ptr (Ptr MicromapUsageEXT)
forall a. Ptr a
nullPtr)
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pMicromap" ::: Ptr MicromapEXT) -> MicromapEXT -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureTrianglesOpacityMicromapEXT
p Ptr AccelerationStructureTrianglesOpacityMicromapEXT
-> Int -> "pMicromap" ::: Ptr MicromapEXT
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
64 :: Ptr MicromapEXT)) (MicromapEXT
forall a. Zero a => a
zero)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f

instance Zero AccelerationStructureTrianglesOpacityMicromapEXT where
  zero :: AccelerationStructureTrianglesOpacityMicromapEXT
zero = IndexType
-> DeviceOrHostAddressConstKHR
-> ("dataSize" ::: Word64)
-> Flags
-> Flags
-> Vector MicromapUsageEXT
-> MicromapEXT
-> AccelerationStructureTrianglesOpacityMicromapEXT
AccelerationStructureTrianglesOpacityMicromapEXT
           IndexType
forall a. Zero a => a
zero
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           Flags
forall a. Zero a => a
zero
           Flags
forall a. Zero a => a
zero
           Vector MicromapUsageEXT
forall a. Monoid a => a
mempty
           MicromapEXT
forall a. Zero a => a
zero


-- | VkMicromapTypeEXT - Type of micromap
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'MicromapBuildInfoEXT', 'MicromapCreateInfoEXT'
newtype MicromapTypeEXT = MicromapTypeEXT Int32
  deriving newtype (MicromapTypeEXT -> MicromapTypeEXT -> Bool
(MicromapTypeEXT -> MicromapTypeEXT -> Bool)
-> (MicromapTypeEXT -> MicromapTypeEXT -> Bool)
-> Eq MicromapTypeEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
$c/= :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
== :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
$c== :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
Eq, Eq MicromapTypeEXT
Eq MicromapTypeEXT
-> (MicromapTypeEXT -> MicromapTypeEXT -> Ordering)
-> (MicromapTypeEXT -> MicromapTypeEXT -> Bool)
-> (MicromapTypeEXT -> MicromapTypeEXT -> Bool)
-> (MicromapTypeEXT -> MicromapTypeEXT -> Bool)
-> (MicromapTypeEXT -> MicromapTypeEXT -> Bool)
-> (MicromapTypeEXT -> MicromapTypeEXT -> MicromapTypeEXT)
-> (MicromapTypeEXT -> MicromapTypeEXT -> MicromapTypeEXT)
-> Ord MicromapTypeEXT
MicromapTypeEXT -> MicromapTypeEXT -> Bool
MicromapTypeEXT -> MicromapTypeEXT -> Ordering
MicromapTypeEXT -> MicromapTypeEXT -> MicromapTypeEXT
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 :: MicromapTypeEXT -> MicromapTypeEXT -> MicromapTypeEXT
$cmin :: MicromapTypeEXT -> MicromapTypeEXT -> MicromapTypeEXT
max :: MicromapTypeEXT -> MicromapTypeEXT -> MicromapTypeEXT
$cmax :: MicromapTypeEXT -> MicromapTypeEXT -> MicromapTypeEXT
>= :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
$c>= :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
> :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
$c> :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
<= :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
$c<= :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
< :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
$c< :: MicromapTypeEXT -> MicromapTypeEXT -> Bool
compare :: MicromapTypeEXT -> MicromapTypeEXT -> Ordering
$ccompare :: MicromapTypeEXT -> MicromapTypeEXT -> Ordering
Ord, Ptr MicromapTypeEXT -> IO MicromapTypeEXT
Ptr MicromapTypeEXT -> Int -> IO MicromapTypeEXT
Ptr MicromapTypeEXT -> Int -> MicromapTypeEXT -> IO ()
Ptr MicromapTypeEXT -> MicromapTypeEXT -> IO ()
MicromapTypeEXT -> Int
(MicromapTypeEXT -> Int)
-> (MicromapTypeEXT -> Int)
-> (Ptr MicromapTypeEXT -> Int -> IO MicromapTypeEXT)
-> (Ptr MicromapTypeEXT -> Int -> MicromapTypeEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO MicromapTypeEXT)
-> (forall b. Ptr b -> Int -> MicromapTypeEXT -> IO ())
-> (Ptr MicromapTypeEXT -> IO MicromapTypeEXT)
-> (Ptr MicromapTypeEXT -> MicromapTypeEXT -> IO ())
-> Storable MicromapTypeEXT
forall b. Ptr b -> Int -> IO MicromapTypeEXT
forall b. Ptr b -> Int -> MicromapTypeEXT -> 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 MicromapTypeEXT -> MicromapTypeEXT -> IO ()
$cpoke :: Ptr MicromapTypeEXT -> MicromapTypeEXT -> IO ()
peek :: Ptr MicromapTypeEXT -> IO MicromapTypeEXT
$cpeek :: Ptr MicromapTypeEXT -> IO MicromapTypeEXT
pokeByteOff :: forall b. Ptr b -> Int -> MicromapTypeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MicromapTypeEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO MicromapTypeEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MicromapTypeEXT
pokeElemOff :: Ptr MicromapTypeEXT -> Int -> MicromapTypeEXT -> IO ()
$cpokeElemOff :: Ptr MicromapTypeEXT -> Int -> MicromapTypeEXT -> IO ()
peekElemOff :: Ptr MicromapTypeEXT -> Int -> IO MicromapTypeEXT
$cpeekElemOff :: Ptr MicromapTypeEXT -> Int -> IO MicromapTypeEXT
alignment :: MicromapTypeEXT -> Int
$calignment :: MicromapTypeEXT -> Int
sizeOf :: MicromapTypeEXT -> Int
$csizeOf :: MicromapTypeEXT -> Int
Storable, MicromapTypeEXT
MicromapTypeEXT -> Zero MicromapTypeEXT
forall a. a -> Zero a
zero :: MicromapTypeEXT
$czero :: MicromapTypeEXT
Zero)

-- | 'MICROMAP_TYPE_OPACITY_MICROMAP_EXT' is a micromap containing data to
-- control the opacity of a triangle
pattern $bMICROMAP_TYPE_OPACITY_MICROMAP_EXT :: MicromapTypeEXT
$mMICROMAP_TYPE_OPACITY_MICROMAP_EXT :: forall {r}. MicromapTypeEXT -> (Void# -> r) -> (Void# -> r) -> r
MICROMAP_TYPE_OPACITY_MICROMAP_EXT = MicromapTypeEXT 0

{-# COMPLETE MICROMAP_TYPE_OPACITY_MICROMAP_EXT :: MicromapTypeEXT #-}

conNameMicromapTypeEXT :: String
conNameMicromapTypeEXT :: String
conNameMicromapTypeEXT = String
"MicromapTypeEXT"

enumPrefixMicromapTypeEXT :: String
enumPrefixMicromapTypeEXT :: String
enumPrefixMicromapTypeEXT = String
"MICROMAP_TYPE_OPACITY_MICROMAP_EXT"

showTableMicromapTypeEXT :: [(MicromapTypeEXT, String)]
showTableMicromapTypeEXT :: [(MicromapTypeEXT, String)]
showTableMicromapTypeEXT = [(MicromapTypeEXT
MICROMAP_TYPE_OPACITY_MICROMAP_EXT, String
"")]

instance Show MicromapTypeEXT where
  showsPrec :: Int -> MicromapTypeEXT -> ShowS
showsPrec =
    String
-> [(MicromapTypeEXT, String)]
-> String
-> (MicromapTypeEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> MicromapTypeEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixMicromapTypeEXT
      [(MicromapTypeEXT, String)]
showTableMicromapTypeEXT
      String
conNameMicromapTypeEXT
      (\(MicromapTypeEXT Int32
x) -> Int32
x)
      (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read MicromapTypeEXT where
  readPrec :: ReadPrec MicromapTypeEXT
readPrec =
    String
-> [(MicromapTypeEXT, String)]
-> String
-> (Int32 -> MicromapTypeEXT)
-> ReadPrec MicromapTypeEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixMicromapTypeEXT
      [(MicromapTypeEXT, String)]
showTableMicromapTypeEXT
      String
conNameMicromapTypeEXT
      Int32 -> MicromapTypeEXT
MicromapTypeEXT

type BuildMicromapFlagsEXT = BuildMicromapFlagBitsEXT

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

-- | 'BUILD_MICROMAP_PREFER_FAST_TRACE_BIT_EXT' indicates that the given
-- micromap build /should/ prioritize trace performance over build time.
pattern $bBUILD_MICROMAP_PREFER_FAST_TRACE_BIT_EXT :: BuildMicromapFlagBitsEXT
$mBUILD_MICROMAP_PREFER_FAST_TRACE_BIT_EXT :: forall {r}.
BuildMicromapFlagBitsEXT -> (Void# -> r) -> (Void# -> r) -> r
BUILD_MICROMAP_PREFER_FAST_TRACE_BIT_EXT = BuildMicromapFlagBitsEXT 0x00000001

-- | 'BUILD_MICROMAP_PREFER_FAST_BUILD_BIT_EXT' indicates that the given
-- micromap build /should/ prioritize build time over trace performance.
pattern $bBUILD_MICROMAP_PREFER_FAST_BUILD_BIT_EXT :: BuildMicromapFlagBitsEXT
$mBUILD_MICROMAP_PREFER_FAST_BUILD_BIT_EXT :: forall {r}.
BuildMicromapFlagBitsEXT -> (Void# -> r) -> (Void# -> r) -> r
BUILD_MICROMAP_PREFER_FAST_BUILD_BIT_EXT = BuildMicromapFlagBitsEXT 0x00000002

-- No documentation found for Nested "VkBuildMicromapFlagBitsEXT" "VK_BUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT"
pattern $bBUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT :: BuildMicromapFlagBitsEXT
$mBUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT :: forall {r}.
BuildMicromapFlagBitsEXT -> (Void# -> r) -> (Void# -> r) -> r
BUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT = BuildMicromapFlagBitsEXT 0x00000004

conNameBuildMicromapFlagBitsEXT :: String
conNameBuildMicromapFlagBitsEXT :: String
conNameBuildMicromapFlagBitsEXT = String
"BuildMicromapFlagBitsEXT"

enumPrefixBuildMicromapFlagBitsEXT :: String
enumPrefixBuildMicromapFlagBitsEXT :: String
enumPrefixBuildMicromapFlagBitsEXT = String
"BUILD_MICROMAP_"

showTableBuildMicromapFlagBitsEXT :: [(BuildMicromapFlagBitsEXT, String)]
showTableBuildMicromapFlagBitsEXT :: [(BuildMicromapFlagBitsEXT, String)]
showTableBuildMicromapFlagBitsEXT =
  [
    ( BuildMicromapFlagBitsEXT
BUILD_MICROMAP_PREFER_FAST_TRACE_BIT_EXT
    , String
"PREFER_FAST_TRACE_BIT_EXT"
    )
  ,
    ( BuildMicromapFlagBitsEXT
BUILD_MICROMAP_PREFER_FAST_BUILD_BIT_EXT
    , String
"PREFER_FAST_BUILD_BIT_EXT"
    )
  ,
    ( BuildMicromapFlagBitsEXT
BUILD_MICROMAP_ALLOW_COMPACTION_BIT_EXT
    , String
"ALLOW_COMPACTION_BIT_EXT"
    )
  ]

instance Show BuildMicromapFlagBitsEXT where
  showsPrec :: Int -> BuildMicromapFlagBitsEXT -> ShowS
showsPrec =
    String
-> [(BuildMicromapFlagBitsEXT, String)]
-> String
-> (BuildMicromapFlagBitsEXT -> Flags)
-> (Flags -> ShowS)
-> Int
-> BuildMicromapFlagBitsEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixBuildMicromapFlagBitsEXT
      [(BuildMicromapFlagBitsEXT, String)]
showTableBuildMicromapFlagBitsEXT
      String
conNameBuildMicromapFlagBitsEXT
      (\(BuildMicromapFlagBitsEXT Flags
x) -> Flags
x)
      (\Flags
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read BuildMicromapFlagBitsEXT where
  readPrec :: ReadPrec BuildMicromapFlagBitsEXT
readPrec =
    String
-> [(BuildMicromapFlagBitsEXT, String)]
-> String
-> (Flags -> BuildMicromapFlagBitsEXT)
-> ReadPrec BuildMicromapFlagBitsEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixBuildMicromapFlagBitsEXT
      [(BuildMicromapFlagBitsEXT, String)]
showTableBuildMicromapFlagBitsEXT
      String
conNameBuildMicromapFlagBitsEXT
      Flags -> BuildMicromapFlagBitsEXT
BuildMicromapFlagBitsEXT

type MicromapCreateFlagsEXT = MicromapCreateFlagBitsEXT

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

-- | 'MICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT' specifies that
-- the micromap’s address /can/ be saved and reused on a subsequent run.
pattern $bMICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT :: MicromapCreateFlagBitsEXT
$mMICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT :: forall {r}.
MicromapCreateFlagBitsEXT -> (Void# -> r) -> (Void# -> r) -> r
MICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT = MicromapCreateFlagBitsEXT 0x00000001

conNameMicromapCreateFlagBitsEXT :: String
conNameMicromapCreateFlagBitsEXT :: String
conNameMicromapCreateFlagBitsEXT = String
"MicromapCreateFlagBitsEXT"

enumPrefixMicromapCreateFlagBitsEXT :: String
enumPrefixMicromapCreateFlagBitsEXT :: String
enumPrefixMicromapCreateFlagBitsEXT = String
"MICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT"

showTableMicromapCreateFlagBitsEXT :: [(MicromapCreateFlagBitsEXT, String)]
showTableMicromapCreateFlagBitsEXT :: [(MicromapCreateFlagBitsEXT, String)]
showTableMicromapCreateFlagBitsEXT =
  [
    ( MicromapCreateFlagBitsEXT
MICROMAP_CREATE_DEVICE_ADDRESS_CAPTURE_REPLAY_BIT_EXT
    , String
""
    )
  ]

instance Show MicromapCreateFlagBitsEXT where
  showsPrec :: Int -> MicromapCreateFlagBitsEXT -> ShowS
showsPrec =
    String
-> [(MicromapCreateFlagBitsEXT, String)]
-> String
-> (MicromapCreateFlagBitsEXT -> Flags)
-> (Flags -> ShowS)
-> Int
-> MicromapCreateFlagBitsEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixMicromapCreateFlagBitsEXT
      [(MicromapCreateFlagBitsEXT, String)]
showTableMicromapCreateFlagBitsEXT
      String
conNameMicromapCreateFlagBitsEXT
      (\(MicromapCreateFlagBitsEXT Flags
x) -> Flags
x)
      (\Flags
x -> String -> ShowS
showString String
"0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flags -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex Flags
x)

instance Read MicromapCreateFlagBitsEXT where
  readPrec :: ReadPrec MicromapCreateFlagBitsEXT
readPrec =
    String
-> [(MicromapCreateFlagBitsEXT, String)]
-> String
-> (Flags -> MicromapCreateFlagBitsEXT)
-> ReadPrec MicromapCreateFlagBitsEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixMicromapCreateFlagBitsEXT
      [(MicromapCreateFlagBitsEXT, String)]
showTableMicromapCreateFlagBitsEXT
      String
conNameMicromapCreateFlagBitsEXT
      Flags -> MicromapCreateFlagBitsEXT
MicromapCreateFlagBitsEXT

-- | VkCopyMicromapModeEXT - Micromap copy mode
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'CopyMemoryToMicromapInfoEXT', 'CopyMicromapInfoEXT',
-- 'CopyMicromapToMemoryInfoEXT'
newtype CopyMicromapModeEXT = CopyMicromapModeEXT Int32
  deriving newtype (CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
(CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool)
-> (CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool)
-> Eq CopyMicromapModeEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
$c/= :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
== :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
$c== :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
Eq, Eq CopyMicromapModeEXT
Eq CopyMicromapModeEXT
-> (CopyMicromapModeEXT -> CopyMicromapModeEXT -> Ordering)
-> (CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool)
-> (CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool)
-> (CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool)
-> (CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool)
-> (CopyMicromapModeEXT
    -> CopyMicromapModeEXT -> CopyMicromapModeEXT)
-> (CopyMicromapModeEXT
    -> CopyMicromapModeEXT -> CopyMicromapModeEXT)
-> Ord CopyMicromapModeEXT
CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
CopyMicromapModeEXT -> CopyMicromapModeEXT -> Ordering
CopyMicromapModeEXT -> CopyMicromapModeEXT -> CopyMicromapModeEXT
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 :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> CopyMicromapModeEXT
$cmin :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> CopyMicromapModeEXT
max :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> CopyMicromapModeEXT
$cmax :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> CopyMicromapModeEXT
>= :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
$c>= :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
> :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
$c> :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
<= :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
$c<= :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
< :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
$c< :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Bool
compare :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Ordering
$ccompare :: CopyMicromapModeEXT -> CopyMicromapModeEXT -> Ordering
Ord, Ptr CopyMicromapModeEXT -> IO CopyMicromapModeEXT
Ptr CopyMicromapModeEXT -> Int -> IO CopyMicromapModeEXT
Ptr CopyMicromapModeEXT -> Int -> CopyMicromapModeEXT -> IO ()
Ptr CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ()
CopyMicromapModeEXT -> Int
(CopyMicromapModeEXT -> Int)
-> (CopyMicromapModeEXT -> Int)
-> (Ptr CopyMicromapModeEXT -> Int -> IO CopyMicromapModeEXT)
-> (Ptr CopyMicromapModeEXT -> Int -> CopyMicromapModeEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO CopyMicromapModeEXT)
-> (forall b. Ptr b -> Int -> CopyMicromapModeEXT -> IO ())
-> (Ptr CopyMicromapModeEXT -> IO CopyMicromapModeEXT)
-> (Ptr CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ())
-> Storable CopyMicromapModeEXT
forall b. Ptr b -> Int -> IO CopyMicromapModeEXT
forall b. Ptr b -> Int -> CopyMicromapModeEXT -> 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 CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ()
$cpoke :: Ptr CopyMicromapModeEXT -> CopyMicromapModeEXT -> IO ()
peek :: Ptr CopyMicromapModeEXT -> IO CopyMicromapModeEXT
$cpeek :: Ptr CopyMicromapModeEXT -> IO CopyMicromapModeEXT
pokeByteOff :: forall b. Ptr b -> Int -> CopyMicromapModeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CopyMicromapModeEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO CopyMicromapModeEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CopyMicromapModeEXT
pokeElemOff :: Ptr CopyMicromapModeEXT -> Int -> CopyMicromapModeEXT -> IO ()
$cpokeElemOff :: Ptr CopyMicromapModeEXT -> Int -> CopyMicromapModeEXT -> IO ()
peekElemOff :: Ptr CopyMicromapModeEXT -> Int -> IO CopyMicromapModeEXT
$cpeekElemOff :: Ptr CopyMicromapModeEXT -> Int -> IO CopyMicromapModeEXT
alignment :: CopyMicromapModeEXT -> Int
$calignment :: CopyMicromapModeEXT -> Int
sizeOf :: CopyMicromapModeEXT -> Int
$csizeOf :: CopyMicromapModeEXT -> Int
Storable, CopyMicromapModeEXT
CopyMicromapModeEXT -> Zero CopyMicromapModeEXT
forall a. a -> Zero a
zero :: CopyMicromapModeEXT
$czero :: CopyMicromapModeEXT
Zero)

-- | 'COPY_MICROMAP_MODE_CLONE_EXT' creates a direct copy of the micromap
-- specified in @src@ into the one specified by @dst@. The @dst@ micromap
-- /must/ have been created with the same parameters as @src@.
pattern $bCOPY_MICROMAP_MODE_CLONE_EXT :: CopyMicromapModeEXT
$mCOPY_MICROMAP_MODE_CLONE_EXT :: forall {r}.
CopyMicromapModeEXT -> (Void# -> r) -> (Void# -> r) -> r
COPY_MICROMAP_MODE_CLONE_EXT = CopyMicromapModeEXT 0

-- | 'COPY_MICROMAP_MODE_SERIALIZE_EXT' serializes the micromap to a
-- semi-opaque format which can be reloaded on a compatible implementation.
pattern $bCOPY_MICROMAP_MODE_SERIALIZE_EXT :: CopyMicromapModeEXT
$mCOPY_MICROMAP_MODE_SERIALIZE_EXT :: forall {r}.
CopyMicromapModeEXT -> (Void# -> r) -> (Void# -> r) -> r
COPY_MICROMAP_MODE_SERIALIZE_EXT = CopyMicromapModeEXT 1

-- | 'COPY_MICROMAP_MODE_DESERIALIZE_EXT' deserializes the semi-opaque
-- serialization format in the buffer to the micromap.
pattern $bCOPY_MICROMAP_MODE_DESERIALIZE_EXT :: CopyMicromapModeEXT
$mCOPY_MICROMAP_MODE_DESERIALIZE_EXT :: forall {r}.
CopyMicromapModeEXT -> (Void# -> r) -> (Void# -> r) -> r
COPY_MICROMAP_MODE_DESERIALIZE_EXT = CopyMicromapModeEXT 2

-- | 'COPY_MICROMAP_MODE_COMPACT_EXT' creates a more compact version of a
-- micromap @src@ into @dst@. The micromap @dst@ /must/ have been created
-- with a size at least as large as that returned by
-- 'cmdWriteMicromapsPropertiesEXT' after the build of the micromap
-- specified by @src@.
pattern $bCOPY_MICROMAP_MODE_COMPACT_EXT :: CopyMicromapModeEXT
$mCOPY_MICROMAP_MODE_COMPACT_EXT :: forall {r}.
CopyMicromapModeEXT -> (Void# -> r) -> (Void# -> r) -> r
COPY_MICROMAP_MODE_COMPACT_EXT = CopyMicromapModeEXT 3

{-# COMPLETE
  COPY_MICROMAP_MODE_CLONE_EXT
  , COPY_MICROMAP_MODE_SERIALIZE_EXT
  , COPY_MICROMAP_MODE_DESERIALIZE_EXT
  , COPY_MICROMAP_MODE_COMPACT_EXT ::
    CopyMicromapModeEXT
  #-}

conNameCopyMicromapModeEXT :: String
conNameCopyMicromapModeEXT :: String
conNameCopyMicromapModeEXT = String
"CopyMicromapModeEXT"

enumPrefixCopyMicromapModeEXT :: String
enumPrefixCopyMicromapModeEXT :: String
enumPrefixCopyMicromapModeEXT = String
"COPY_MICROMAP_MODE_"

showTableCopyMicromapModeEXT :: [(CopyMicromapModeEXT, String)]
showTableCopyMicromapModeEXT :: [(CopyMicromapModeEXT, String)]
showTableCopyMicromapModeEXT =
  [ (CopyMicromapModeEXT
COPY_MICROMAP_MODE_CLONE_EXT, String
"CLONE_EXT")
  ,
    ( CopyMicromapModeEXT
COPY_MICROMAP_MODE_SERIALIZE_EXT
    , String
"SERIALIZE_EXT"
    )
  ,
    ( CopyMicromapModeEXT
COPY_MICROMAP_MODE_DESERIALIZE_EXT
    , String
"DESERIALIZE_EXT"
    )
  ,
    ( CopyMicromapModeEXT
COPY_MICROMAP_MODE_COMPACT_EXT
    , String
"COMPACT_EXT"
    )
  ]

instance Show CopyMicromapModeEXT where
  showsPrec :: Int -> CopyMicromapModeEXT -> ShowS
showsPrec =
    String
-> [(CopyMicromapModeEXT, String)]
-> String
-> (CopyMicromapModeEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> CopyMicromapModeEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixCopyMicromapModeEXT
      [(CopyMicromapModeEXT, String)]
showTableCopyMicromapModeEXT
      String
conNameCopyMicromapModeEXT
      (\(CopyMicromapModeEXT Int32
x) -> Int32
x)
      (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read CopyMicromapModeEXT where
  readPrec :: ReadPrec CopyMicromapModeEXT
readPrec =
    String
-> [(CopyMicromapModeEXT, String)]
-> String
-> (Int32 -> CopyMicromapModeEXT)
-> ReadPrec CopyMicromapModeEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixCopyMicromapModeEXT
      [(CopyMicromapModeEXT, String)]
showTableCopyMicromapModeEXT
      String
conNameCopyMicromapModeEXT
      Int32 -> CopyMicromapModeEXT
CopyMicromapModeEXT

-- | VkBuildMicromapModeEXT - Enum specifying the type of build operation to
-- perform
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>,
-- 'MicromapBuildInfoEXT'
newtype BuildMicromapModeEXT = BuildMicromapModeEXT Int32
  deriving newtype (BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
(BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool)
-> (BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool)
-> Eq BuildMicromapModeEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
$c/= :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
== :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
$c== :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
Eq, Eq BuildMicromapModeEXT
Eq BuildMicromapModeEXT
-> (BuildMicromapModeEXT -> BuildMicromapModeEXT -> Ordering)
-> (BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool)
-> (BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool)
-> (BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool)
-> (BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool)
-> (BuildMicromapModeEXT
    -> BuildMicromapModeEXT -> BuildMicromapModeEXT)
-> (BuildMicromapModeEXT
    -> BuildMicromapModeEXT -> BuildMicromapModeEXT)
-> Ord BuildMicromapModeEXT
BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
BuildMicromapModeEXT -> BuildMicromapModeEXT -> Ordering
BuildMicromapModeEXT
-> BuildMicromapModeEXT -> BuildMicromapModeEXT
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 :: BuildMicromapModeEXT
-> BuildMicromapModeEXT -> BuildMicromapModeEXT
$cmin :: BuildMicromapModeEXT
-> BuildMicromapModeEXT -> BuildMicromapModeEXT
max :: BuildMicromapModeEXT
-> BuildMicromapModeEXT -> BuildMicromapModeEXT
$cmax :: BuildMicromapModeEXT
-> BuildMicromapModeEXT -> BuildMicromapModeEXT
>= :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
$c>= :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
> :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
$c> :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
<= :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
$c<= :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
< :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
$c< :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Bool
compare :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Ordering
$ccompare :: BuildMicromapModeEXT -> BuildMicromapModeEXT -> Ordering
Ord, Ptr BuildMicromapModeEXT -> IO BuildMicromapModeEXT
Ptr BuildMicromapModeEXT -> Int -> IO BuildMicromapModeEXT
Ptr BuildMicromapModeEXT -> Int -> BuildMicromapModeEXT -> IO ()
Ptr BuildMicromapModeEXT -> BuildMicromapModeEXT -> IO ()
BuildMicromapModeEXT -> Int
(BuildMicromapModeEXT -> Int)
-> (BuildMicromapModeEXT -> Int)
-> (Ptr BuildMicromapModeEXT -> Int -> IO BuildMicromapModeEXT)
-> (Ptr BuildMicromapModeEXT
    -> Int -> BuildMicromapModeEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO BuildMicromapModeEXT)
-> (forall b. Ptr b -> Int -> BuildMicromapModeEXT -> IO ())
-> (Ptr BuildMicromapModeEXT -> IO BuildMicromapModeEXT)
-> (Ptr BuildMicromapModeEXT -> BuildMicromapModeEXT -> IO ())
-> Storable BuildMicromapModeEXT
forall b. Ptr b -> Int -> IO BuildMicromapModeEXT
forall b. Ptr b -> Int -> BuildMicromapModeEXT -> 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 BuildMicromapModeEXT -> BuildMicromapModeEXT -> IO ()
$cpoke :: Ptr BuildMicromapModeEXT -> BuildMicromapModeEXT -> IO ()
peek :: Ptr BuildMicromapModeEXT -> IO BuildMicromapModeEXT
$cpeek :: Ptr BuildMicromapModeEXT -> IO BuildMicromapModeEXT
pokeByteOff :: forall b. Ptr b -> Int -> BuildMicromapModeEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> BuildMicromapModeEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO BuildMicromapModeEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO BuildMicromapModeEXT
pokeElemOff :: Ptr BuildMicromapModeEXT -> Int -> BuildMicromapModeEXT -> IO ()
$cpokeElemOff :: Ptr BuildMicromapModeEXT -> Int -> BuildMicromapModeEXT -> IO ()
peekElemOff :: Ptr BuildMicromapModeEXT -> Int -> IO BuildMicromapModeEXT
$cpeekElemOff :: Ptr BuildMicromapModeEXT -> Int -> IO BuildMicromapModeEXT
alignment :: BuildMicromapModeEXT -> Int
$calignment :: BuildMicromapModeEXT -> Int
sizeOf :: BuildMicromapModeEXT -> Int
$csizeOf :: BuildMicromapModeEXT -> Int
Storable, BuildMicromapModeEXT
BuildMicromapModeEXT -> Zero BuildMicromapModeEXT
forall a. a -> Zero a
zero :: BuildMicromapModeEXT
$czero :: BuildMicromapModeEXT
Zero)

-- | 'BUILD_MICROMAP_MODE_BUILD_EXT' specifies that the destination micromap
-- will be built using the specified data.
pattern $bBUILD_MICROMAP_MODE_BUILD_EXT :: BuildMicromapModeEXT
$mBUILD_MICROMAP_MODE_BUILD_EXT :: forall {r}.
BuildMicromapModeEXT -> (Void# -> r) -> (Void# -> r) -> r
BUILD_MICROMAP_MODE_BUILD_EXT = BuildMicromapModeEXT 0

{-# COMPLETE BUILD_MICROMAP_MODE_BUILD_EXT :: BuildMicromapModeEXT #-}

conNameBuildMicromapModeEXT :: String
conNameBuildMicromapModeEXT :: String
conNameBuildMicromapModeEXT = String
"BuildMicromapModeEXT"

enumPrefixBuildMicromapModeEXT :: String
enumPrefixBuildMicromapModeEXT :: String
enumPrefixBuildMicromapModeEXT = String
"BUILD_MICROMAP_MODE_BUILD_EXT"

showTableBuildMicromapModeEXT :: [(BuildMicromapModeEXT, String)]
showTableBuildMicromapModeEXT :: [(BuildMicromapModeEXT, String)]
showTableBuildMicromapModeEXT = [(BuildMicromapModeEXT
BUILD_MICROMAP_MODE_BUILD_EXT, String
"")]

instance Show BuildMicromapModeEXT where
  showsPrec :: Int -> BuildMicromapModeEXT -> ShowS
showsPrec =
    String
-> [(BuildMicromapModeEXT, String)]
-> String
-> (BuildMicromapModeEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> BuildMicromapModeEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixBuildMicromapModeEXT
      [(BuildMicromapModeEXT, String)]
showTableBuildMicromapModeEXT
      String
conNameBuildMicromapModeEXT
      (\(BuildMicromapModeEXT Int32
x) -> Int32
x)
      (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read BuildMicromapModeEXT where
  readPrec :: ReadPrec BuildMicromapModeEXT
readPrec =
    String
-> [(BuildMicromapModeEXT, String)]
-> String
-> (Int32 -> BuildMicromapModeEXT)
-> ReadPrec BuildMicromapModeEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixBuildMicromapModeEXT
      [(BuildMicromapModeEXT, String)]
showTableBuildMicromapModeEXT
      String
conNameBuildMicromapModeEXT
      Int32 -> BuildMicromapModeEXT
BuildMicromapModeEXT

-- | VkOpacityMicromapFormatEXT - Format enum for opacity micromaps
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>
newtype OpacityMicromapFormatEXT = OpacityMicromapFormatEXT Int32
  deriving newtype (OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
(OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool)
-> (OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool)
-> Eq OpacityMicromapFormatEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
$c/= :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
== :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
$c== :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
Eq, Eq OpacityMicromapFormatEXT
Eq OpacityMicromapFormatEXT
-> (OpacityMicromapFormatEXT
    -> OpacityMicromapFormatEXT -> Ordering)
-> (OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool)
-> (OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool)
-> (OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool)
-> (OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool)
-> (OpacityMicromapFormatEXT
    -> OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT)
-> (OpacityMicromapFormatEXT
    -> OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT)
-> Ord OpacityMicromapFormatEXT
OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Ordering
OpacityMicromapFormatEXT
-> OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT
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 :: OpacityMicromapFormatEXT
-> OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT
$cmin :: OpacityMicromapFormatEXT
-> OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT
max :: OpacityMicromapFormatEXT
-> OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT
$cmax :: OpacityMicromapFormatEXT
-> OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT
>= :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
$c>= :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
> :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
$c> :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
<= :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
$c<= :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
< :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
$c< :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Bool
compare :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Ordering
$ccompare :: OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> Ordering
Ord, Ptr OpacityMicromapFormatEXT -> IO OpacityMicromapFormatEXT
Ptr OpacityMicromapFormatEXT -> Int -> IO OpacityMicromapFormatEXT
Ptr OpacityMicromapFormatEXT
-> Int -> OpacityMicromapFormatEXT -> IO ()
Ptr OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> IO ()
OpacityMicromapFormatEXT -> Int
(OpacityMicromapFormatEXT -> Int)
-> (OpacityMicromapFormatEXT -> Int)
-> (Ptr OpacityMicromapFormatEXT
    -> Int -> IO OpacityMicromapFormatEXT)
-> (Ptr OpacityMicromapFormatEXT
    -> Int -> OpacityMicromapFormatEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO OpacityMicromapFormatEXT)
-> (forall b. Ptr b -> Int -> OpacityMicromapFormatEXT -> IO ())
-> (Ptr OpacityMicromapFormatEXT -> IO OpacityMicromapFormatEXT)
-> (Ptr OpacityMicromapFormatEXT
    -> OpacityMicromapFormatEXT -> IO ())
-> Storable OpacityMicromapFormatEXT
forall b. Ptr b -> Int -> IO OpacityMicromapFormatEXT
forall b. Ptr b -> Int -> OpacityMicromapFormatEXT -> 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 OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> IO ()
$cpoke :: Ptr OpacityMicromapFormatEXT -> OpacityMicromapFormatEXT -> IO ()
peek :: Ptr OpacityMicromapFormatEXT -> IO OpacityMicromapFormatEXT
$cpeek :: Ptr OpacityMicromapFormatEXT -> IO OpacityMicromapFormatEXT
pokeByteOff :: forall b. Ptr b -> Int -> OpacityMicromapFormatEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> OpacityMicromapFormatEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO OpacityMicromapFormatEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO OpacityMicromapFormatEXT
pokeElemOff :: Ptr OpacityMicromapFormatEXT
-> Int -> OpacityMicromapFormatEXT -> IO ()
$cpokeElemOff :: Ptr OpacityMicromapFormatEXT
-> Int -> OpacityMicromapFormatEXT -> IO ()
peekElemOff :: Ptr OpacityMicromapFormatEXT -> Int -> IO OpacityMicromapFormatEXT
$cpeekElemOff :: Ptr OpacityMicromapFormatEXT -> Int -> IO OpacityMicromapFormatEXT
alignment :: OpacityMicromapFormatEXT -> Int
$calignment :: OpacityMicromapFormatEXT -> Int
sizeOf :: OpacityMicromapFormatEXT -> Int
$csizeOf :: OpacityMicromapFormatEXT -> Int
Storable, OpacityMicromapFormatEXT
OpacityMicromapFormatEXT -> Zero OpacityMicromapFormatEXT
forall a. a -> Zero a
zero :: OpacityMicromapFormatEXT
$czero :: OpacityMicromapFormatEXT
Zero)

-- Note that the zero instance does not produce a valid value, passing 'zero' to Vulkan will result in an error

-- | 'OPACITY_MICROMAP_FORMAT_2_STATE_EXT' indicates that the given micromap
-- format has one bit per subtriangle encoding either fully opaque or fully
-- transparent.
pattern $bOPACITY_MICROMAP_FORMAT_2_STATE_EXT :: OpacityMicromapFormatEXT
$mOPACITY_MICROMAP_FORMAT_2_STATE_EXT :: forall {r}.
OpacityMicromapFormatEXT -> (Void# -> r) -> (Void# -> r) -> r
OPACITY_MICROMAP_FORMAT_2_STATE_EXT = OpacityMicromapFormatEXT 1

-- | 'OPACITY_MICROMAP_FORMAT_4_STATE_EXT' indicates that the given micromap
-- format has two bits per subtriangle encoding four modes which can be
-- interpreted as described in
-- <https://registry.khronos.org/vulkan/specs/1.3-extensions/html/vkspec.html#ray-opacity-micromap ray traversal>.
pattern $bOPACITY_MICROMAP_FORMAT_4_STATE_EXT :: OpacityMicromapFormatEXT
$mOPACITY_MICROMAP_FORMAT_4_STATE_EXT :: forall {r}.
OpacityMicromapFormatEXT -> (Void# -> r) -> (Void# -> r) -> r
OPACITY_MICROMAP_FORMAT_4_STATE_EXT = OpacityMicromapFormatEXT 2

{-# COMPLETE
  OPACITY_MICROMAP_FORMAT_2_STATE_EXT
  , OPACITY_MICROMAP_FORMAT_4_STATE_EXT ::
    OpacityMicromapFormatEXT
  #-}

conNameOpacityMicromapFormatEXT :: String
conNameOpacityMicromapFormatEXT :: String
conNameOpacityMicromapFormatEXT = String
"OpacityMicromapFormatEXT"

enumPrefixOpacityMicromapFormatEXT :: String
enumPrefixOpacityMicromapFormatEXT :: String
enumPrefixOpacityMicromapFormatEXT = String
"OPACITY_MICROMAP_FORMAT_"

showTableOpacityMicromapFormatEXT :: [(OpacityMicromapFormatEXT, String)]
showTableOpacityMicromapFormatEXT :: [(OpacityMicromapFormatEXT, String)]
showTableOpacityMicromapFormatEXT =
  [
    ( OpacityMicromapFormatEXT
OPACITY_MICROMAP_FORMAT_2_STATE_EXT
    , String
"2_STATE_EXT"
    )
  ,
    ( OpacityMicromapFormatEXT
OPACITY_MICROMAP_FORMAT_4_STATE_EXT
    , String
"4_STATE_EXT"
    )
  ]

instance Show OpacityMicromapFormatEXT where
  showsPrec :: Int -> OpacityMicromapFormatEXT -> ShowS
showsPrec =
    String
-> [(OpacityMicromapFormatEXT, String)]
-> String
-> (OpacityMicromapFormatEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> OpacityMicromapFormatEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixOpacityMicromapFormatEXT
      [(OpacityMicromapFormatEXT, String)]
showTableOpacityMicromapFormatEXT
      String
conNameOpacityMicromapFormatEXT
      (\(OpacityMicromapFormatEXT Int32
x) -> Int32
x)
      (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read OpacityMicromapFormatEXT where
  readPrec :: ReadPrec OpacityMicromapFormatEXT
readPrec =
    String
-> [(OpacityMicromapFormatEXT, String)]
-> String
-> (Int32 -> OpacityMicromapFormatEXT)
-> ReadPrec OpacityMicromapFormatEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixOpacityMicromapFormatEXT
      [(OpacityMicromapFormatEXT, String)]
showTableOpacityMicromapFormatEXT
      String
conNameOpacityMicromapFormatEXT
      Int32 -> OpacityMicromapFormatEXT
OpacityMicromapFormatEXT

-- | VkOpacityMicromapSpecialIndexEXT - Enum for special indices in the
-- opacity micromap
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_EXT_opacity_micromap VK_EXT_opacity_micromap>
newtype OpacityMicromapSpecialIndexEXT = OpacityMicromapSpecialIndexEXT Int32
  deriving newtype (OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
(OpacityMicromapSpecialIndexEXT
 -> OpacityMicromapSpecialIndexEXT -> Bool)
-> (OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT -> Bool)
-> Eq OpacityMicromapSpecialIndexEXT
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
$c/= :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
== :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
$c== :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
Eq, Eq OpacityMicromapSpecialIndexEXT
Eq OpacityMicromapSpecialIndexEXT
-> (OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT -> Ordering)
-> (OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT -> Bool)
-> (OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT -> Bool)
-> (OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT -> Bool)
-> (OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT -> Bool)
-> (OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT)
-> (OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT)
-> Ord OpacityMicromapSpecialIndexEXT
OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Ordering
OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> OpacityMicromapSpecialIndexEXT
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 :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> OpacityMicromapSpecialIndexEXT
$cmin :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> OpacityMicromapSpecialIndexEXT
max :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> OpacityMicromapSpecialIndexEXT
$cmax :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> OpacityMicromapSpecialIndexEXT
>= :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
$c>= :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
> :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
$c> :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
<= :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
$c<= :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
< :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
$c< :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Bool
compare :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Ordering
$ccompare :: OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> Ordering
Ord, Ptr OpacityMicromapSpecialIndexEXT
-> IO OpacityMicromapSpecialIndexEXT
Ptr OpacityMicromapSpecialIndexEXT
-> Int -> IO OpacityMicromapSpecialIndexEXT
Ptr OpacityMicromapSpecialIndexEXT
-> Int -> OpacityMicromapSpecialIndexEXT -> IO ()
Ptr OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> IO ()
OpacityMicromapSpecialIndexEXT -> Int
(OpacityMicromapSpecialIndexEXT -> Int)
-> (OpacityMicromapSpecialIndexEXT -> Int)
-> (Ptr OpacityMicromapSpecialIndexEXT
    -> Int -> IO OpacityMicromapSpecialIndexEXT)
-> (Ptr OpacityMicromapSpecialIndexEXT
    -> Int -> OpacityMicromapSpecialIndexEXT -> IO ())
-> (forall b. Ptr b -> Int -> IO OpacityMicromapSpecialIndexEXT)
-> (forall b.
    Ptr b -> Int -> OpacityMicromapSpecialIndexEXT -> IO ())
-> (Ptr OpacityMicromapSpecialIndexEXT
    -> IO OpacityMicromapSpecialIndexEXT)
-> (Ptr OpacityMicromapSpecialIndexEXT
    -> OpacityMicromapSpecialIndexEXT -> IO ())
-> Storable OpacityMicromapSpecialIndexEXT
forall b. Ptr b -> Int -> IO OpacityMicromapSpecialIndexEXT
forall b. Ptr b -> Int -> OpacityMicromapSpecialIndexEXT -> 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 OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> IO ()
$cpoke :: Ptr OpacityMicromapSpecialIndexEXT
-> OpacityMicromapSpecialIndexEXT -> IO ()
peek :: Ptr OpacityMicromapSpecialIndexEXT
-> IO OpacityMicromapSpecialIndexEXT
$cpeek :: Ptr OpacityMicromapSpecialIndexEXT
-> IO OpacityMicromapSpecialIndexEXT
pokeByteOff :: forall b. Ptr b -> Int -> OpacityMicromapSpecialIndexEXT -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> OpacityMicromapSpecialIndexEXT -> IO ()
peekByteOff :: forall b. Ptr b -> Int -> IO OpacityMicromapSpecialIndexEXT
$cpeekByteOff :: forall b. Ptr b -> Int -> IO OpacityMicromapSpecialIndexEXT
pokeElemOff :: Ptr OpacityMicromapSpecialIndexEXT
-> Int -> OpacityMicromapSpecialIndexEXT -> IO ()
$cpokeElemOff :: Ptr OpacityMicromapSpecialIndexEXT
-> Int -> OpacityMicromapSpecialIndexEXT -> IO ()
peekElemOff :: Ptr OpacityMicromapSpecialIndexEXT
-> Int -> IO OpacityMicromapSpecialIndexEXT
$cpeekElemOff :: Ptr OpacityMicromapSpecialIndexEXT
-> Int -> IO OpacityMicromapSpecialIndexEXT
alignment :: OpacityMicromapSpecialIndexEXT -> Int
$calignment :: OpacityMicromapSpecialIndexEXT -> Int
sizeOf :: OpacityMicromapSpecialIndexEXT -> Int
$csizeOf :: OpacityMicromapSpecialIndexEXT -> Int
Storable, OpacityMicromapSpecialIndexEXT
OpacityMicromapSpecialIndexEXT
-> Zero OpacityMicromapSpecialIndexEXT
forall a. a -> Zero a
zero :: OpacityMicromapSpecialIndexEXT
$czero :: OpacityMicromapSpecialIndexEXT
Zero)

-- Note that the zero instance does not produce a valid value, passing 'zero' to Vulkan will result in an error

-- | 'OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_TRANSPARENT_EXT' specifies that
-- the entire triangle is fully transparent.
pattern $bOPACITY_MICROMAP_SPECIAL_INDEX_FULLY_TRANSPARENT_EXT :: OpacityMicromapSpecialIndexEXT
$mOPACITY_MICROMAP_SPECIAL_INDEX_FULLY_TRANSPARENT_EXT :: forall {r}.
OpacityMicromapSpecialIndexEXT -> (Void# -> r) -> (Void# -> r) -> r
OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_TRANSPARENT_EXT = OpacityMicromapSpecialIndexEXT (-1)

-- | 'OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_OPAQUE_EXT' specifies that the
-- entire triangle is fully opaque.
pattern $bOPACITY_MICROMAP_SPECIAL_INDEX_FULLY_OPAQUE_EXT :: OpacityMicromapSpecialIndexEXT
$mOPACITY_MICROMAP_SPECIAL_INDEX_FULLY_OPAQUE_EXT :: forall {r}.
OpacityMicromapSpecialIndexEXT -> (Void# -> r) -> (Void# -> r) -> r
OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_OPAQUE_EXT = OpacityMicromapSpecialIndexEXT (-2)

-- | 'OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_TRANSPARENT_EXT' specifies
-- that the entire triangle is unknown-transparent.
pattern $bOPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_TRANSPARENT_EXT :: OpacityMicromapSpecialIndexEXT
$mOPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_TRANSPARENT_EXT :: forall {r}.
OpacityMicromapSpecialIndexEXT -> (Void# -> r) -> (Void# -> r) -> r
OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_TRANSPARENT_EXT = OpacityMicromapSpecialIndexEXT (-3)

-- | 'OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_OPAQUE_EXT' specifies that
-- the entire triangle is unknown-opaque.
pattern $bOPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_OPAQUE_EXT :: OpacityMicromapSpecialIndexEXT
$mOPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_OPAQUE_EXT :: forall {r}.
OpacityMicromapSpecialIndexEXT -> (Void# -> r) -> (Void# -> r) -> r
OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_OPAQUE_EXT = OpacityMicromapSpecialIndexEXT (-4)

{-# COMPLETE
  OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_TRANSPARENT_EXT
  , OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_OPAQUE_EXT
  , OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_TRANSPARENT_EXT
  , OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_OPAQUE_EXT ::
    OpacityMicromapSpecialIndexEXT
  #-}

conNameOpacityMicromapSpecialIndexEXT :: String
conNameOpacityMicromapSpecialIndexEXT :: String
conNameOpacityMicromapSpecialIndexEXT = String
"OpacityMicromapSpecialIndexEXT"

enumPrefixOpacityMicromapSpecialIndexEXT :: String
enumPrefixOpacityMicromapSpecialIndexEXT :: String
enumPrefixOpacityMicromapSpecialIndexEXT = String
"OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_"

showTableOpacityMicromapSpecialIndexEXT :: [(OpacityMicromapSpecialIndexEXT, String)]
showTableOpacityMicromapSpecialIndexEXT :: [(OpacityMicromapSpecialIndexEXT, String)]
showTableOpacityMicromapSpecialIndexEXT =
  [
    ( OpacityMicromapSpecialIndexEXT
OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_TRANSPARENT_EXT
    , String
"TRANSPARENT_EXT"
    )
  ,
    ( OpacityMicromapSpecialIndexEXT
OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_OPAQUE_EXT
    , String
"OPAQUE_EXT"
    )
  ,
    ( OpacityMicromapSpecialIndexEXT
OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_TRANSPARENT_EXT
    , String
"UNKNOWN_TRANSPARENT_EXT"
    )
  ,
    ( OpacityMicromapSpecialIndexEXT
OPACITY_MICROMAP_SPECIAL_INDEX_FULLY_UNKNOWN_OPAQUE_EXT
    , String
"UNKNOWN_OPAQUE_EXT"
    )
  ]

instance Show OpacityMicromapSpecialIndexEXT where
  showsPrec :: Int -> OpacityMicromapSpecialIndexEXT -> ShowS
showsPrec =
    String
-> [(OpacityMicromapSpecialIndexEXT, String)]
-> String
-> (OpacityMicromapSpecialIndexEXT -> Int32)
-> (Int32 -> ShowS)
-> Int
-> OpacityMicromapSpecialIndexEXT
-> ShowS
forall a i.
Eq a =>
String
-> [(a, String)]
-> String
-> (a -> i)
-> (i -> ShowS)
-> Int
-> a
-> ShowS
enumShowsPrec
      String
enumPrefixOpacityMicromapSpecialIndexEXT
      [(OpacityMicromapSpecialIndexEXT, String)]
showTableOpacityMicromapSpecialIndexEXT
      String
conNameOpacityMicromapSpecialIndexEXT
      (\(OpacityMicromapSpecialIndexEXT Int32
x) -> Int32
x)
      (Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11)

instance Read OpacityMicromapSpecialIndexEXT where
  readPrec :: ReadPrec OpacityMicromapSpecialIndexEXT
readPrec =
    String
-> [(OpacityMicromapSpecialIndexEXT, String)]
-> String
-> (Int32 -> OpacityMicromapSpecialIndexEXT)
-> ReadPrec OpacityMicromapSpecialIndexEXT
forall i a.
Read i =>
String -> [(a, String)] -> String -> (i -> a) -> ReadPrec a
enumReadPrec
      String
enumPrefixOpacityMicromapSpecialIndexEXT
      [(OpacityMicromapSpecialIndexEXT, String)]
showTableOpacityMicromapSpecialIndexEXT
      String
conNameOpacityMicromapSpecialIndexEXT
      Int32 -> OpacityMicromapSpecialIndexEXT
OpacityMicromapSpecialIndexEXT

type EXT_OPACITY_MICROMAP_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_EXT_OPACITY_MICROMAP_SPEC_VERSION"
pattern EXT_OPACITY_MICROMAP_SPEC_VERSION :: forall a . Integral a => a
pattern $bEXT_OPACITY_MICROMAP_SPEC_VERSION :: forall a. Integral a => a
$mEXT_OPACITY_MICROMAP_SPEC_VERSION :: forall {r} {a}.
Integral a =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_OPACITY_MICROMAP_SPEC_VERSION = 2


type EXT_OPACITY_MICROMAP_EXTENSION_NAME = "VK_EXT_opacity_micromap"

-- No documentation found for TopLevel "VK_EXT_OPACITY_MICROMAP_EXTENSION_NAME"
pattern EXT_OPACITY_MICROMAP_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bEXT_OPACITY_MICROMAP_EXTENSION_NAME :: forall a. (Eq a, IsString a) => a
$mEXT_OPACITY_MICROMAP_EXTENSION_NAME :: forall {r} {a}.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
EXT_OPACITY_MICROMAP_EXTENSION_NAME = "VK_EXT_opacity_micromap"