{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_ray_tracing  ( destroyAccelerationStructureKHR
                                             , getAccelerationStructureMemoryRequirementsKHR
                                             , bindAccelerationStructureMemoryKHR
                                             , cmdCopyAccelerationStructureKHR
                                             , copyAccelerationStructureKHR
                                             , cmdCopyAccelerationStructureToMemoryKHR
                                             , copyAccelerationStructureToMemoryKHR
                                             , cmdCopyMemoryToAccelerationStructureKHR
                                             , copyMemoryToAccelerationStructureKHR
                                             , cmdWriteAccelerationStructuresPropertiesKHR
                                             , writeAccelerationStructuresPropertiesKHR
                                             , cmdTraceRaysKHR
                                             , getRayTracingShaderGroupHandlesKHR
                                             , getRayTracingCaptureReplayShaderGroupHandlesKHR
                                             , createRayTracingPipelinesKHR
                                             , cmdTraceRaysIndirectKHR
                                             , getDeviceAccelerationStructureCompatibilityKHR
                                             , createAccelerationStructureKHR
                                             , withAccelerationStructureKHR
                                             , cmdBuildAccelerationStructureKHR
                                             , cmdBuildAccelerationStructureIndirectKHR
                                             , buildAccelerationStructureKHR
                                             , getAccelerationStructureDeviceAddressKHR
                                             , RayTracingShaderGroupCreateInfoKHR(..)
                                             , RayTracingPipelineCreateInfoKHR(..)
                                             , BindAccelerationStructureMemoryInfoKHR(..)
                                             , WriteDescriptorSetAccelerationStructureKHR(..)
                                             , AccelerationStructureMemoryRequirementsInfoKHR(..)
                                             , PhysicalDeviceRayTracingFeaturesKHR(..)
                                             , PhysicalDeviceRayTracingPropertiesKHR(..)
                                             , StridedBufferRegionKHR(..)
                                             , TraceRaysIndirectCommandKHR(..)
                                             , AccelerationStructureGeometryTrianglesDataKHR(..)
                                             , AccelerationStructureGeometryAabbsDataKHR(..)
                                             , AccelerationStructureGeometryInstancesDataKHR(..)
                                             , AccelerationStructureGeometryKHR(..)
                                             , AccelerationStructureBuildGeometryInfoKHR(..)
                                             , AccelerationStructureBuildOffsetInfoKHR(..)
                                             , AccelerationStructureCreateGeometryTypeInfoKHR(..)
                                             , AccelerationStructureCreateInfoKHR(..)
                                             , AabbPositionsKHR(..)
                                             , TransformMatrixKHR(..)
                                             , AccelerationStructureInstanceKHR(..)
                                             , AccelerationStructureDeviceAddressInfoKHR(..)
                                             , AccelerationStructureVersionKHR(..)
                                             , CopyAccelerationStructureInfoKHR(..)
                                             , CopyAccelerationStructureToMemoryInfoKHR(..)
                                             , CopyMemoryToAccelerationStructureInfoKHR(..)
                                             , RayTracingPipelineInterfaceCreateInfoKHR(..)
                                             , DeviceOrHostAddressKHR(..)
                                             , DeviceOrHostAddressConstKHR(..)
                                             , AccelerationStructureGeometryDataKHR(..)
                                             , GeometryInstanceFlagBitsKHR( GEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR
                                                                          , GEOMETRY_INSTANCE_TRIANGLE_FRONT_COUNTERCLOCKWISE_BIT_KHR
                                                                          , GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR
                                                                          , GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR
                                                                          , ..
                                                                          )
                                             , GeometryInstanceFlagsKHR
                                             , GeometryFlagBitsKHR( GEOMETRY_OPAQUE_BIT_KHR
                                                                  , GEOMETRY_NO_DUPLICATE_ANY_HIT_INVOCATION_BIT_KHR
                                                                  , ..
                                                                  )
                                             , GeometryFlagsKHR
                                             , BuildAccelerationStructureFlagBitsKHR( BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR
                                                                                    , BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR
                                                                                    , BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR
                                                                                    , BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR
                                                                                    , BUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR
                                                                                    , ..
                                                                                    )
                                             , BuildAccelerationStructureFlagsKHR
                                             , CopyAccelerationStructureModeKHR( COPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR
                                                                               , COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR
                                                                               , COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR
                                                                               , COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR
                                                                               , ..
                                                                               )
                                             , AccelerationStructureTypeKHR( ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR
                                                                           , ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR
                                                                           , ..
                                                                           )
                                             , GeometryTypeKHR( GEOMETRY_TYPE_TRIANGLES_KHR
                                                              , GEOMETRY_TYPE_AABBS_KHR
                                                              , GEOMETRY_TYPE_INSTANCES_KHR
                                                              , ..
                                                              )
                                             , AccelerationStructureMemoryRequirementsTypeKHR( ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR
                                                                                             , ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR
                                                                                             , ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR
                                                                                             , ..
                                                                                             )
                                             , AccelerationStructureBuildTypeKHR( ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR
                                                                                , ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR
                                                                                , ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR
                                                                                , ..
                                                                                )
                                             , RayTracingShaderGroupTypeKHR( RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR
                                                                           , RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR
                                                                           , RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR
                                                                           , ..
                                                                           )
                                             , KHR_RAY_TRACING_SPEC_VERSION
                                             , pattern KHR_RAY_TRACING_SPEC_VERSION
                                             , KHR_RAY_TRACING_EXTENSION_NAME
                                             , pattern KHR_RAY_TRACING_EXTENSION_NAME
                                             , AccelerationStructureKHR(..)
                                             , PipelineLibraryCreateInfoKHR(..)
                                             , DebugReportObjectTypeEXT(..)
                                             , SHADER_UNUSED_KHR
                                             , pattern SHADER_UNUSED_KHR
                                             ) where

import Vulkan.CStruct.Utils (FixedArray)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Bits ((.&.))
import Data.Bits ((.|.))
import Data.Bits (shiftL)
import Data.Bits (shiftR)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import Foreign.Marshal.Utils (maybePeek)
import Foreign.Marshal.Utils (with)
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.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import qualified Data.ByteString (length)
import Data.ByteString (packCStringLen)
import Data.ByteString.Unsafe (unsafeUseAsCString)
import Data.Coerce (coerce)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Control.Monad.Trans.Cont (runContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Foreign.C.Types (CSize(..))
import Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
import Data.String (IsString)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CFloat)
import Foreign.C.Types (CFloat(CFloat))
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 Data.Word (Word32)
import Data.Word (Word64)
import Data.Word (Word8)
import Text.Read.Lex (Lexeme(Ident))
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.Core10.FundamentalTypes (bool32ToBool)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.CStruct.Extends (peekSomeCStruct)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Extensions.Handles (AccelerationStructureKHR)
import Vulkan.Extensions.Handles (AccelerationStructureKHR(..))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.Handles (Buffer)
import Vulkan.Core10.Handles (Buffer(..))
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_deferred_host_operations (DeferredOperationInfoKHR)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.FundamentalTypes (DeviceAddress)
import Vulkan.Dynamic (DeviceCmds(pVkBindAccelerationStructureMemoryKHR))
import Vulkan.Dynamic (DeviceCmds(pVkBuildAccelerationStructureKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBuildAccelerationStructureIndirectKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdBuildAccelerationStructureKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyAccelerationStructureKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyAccelerationStructureToMemoryKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdCopyMemoryToAccelerationStructureKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdTraceRaysIndirectKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdTraceRaysKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdWriteAccelerationStructuresPropertiesKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCopyAccelerationStructureKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCopyAccelerationStructureToMemoryKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCopyMemoryToAccelerationStructureKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCreateAccelerationStructureKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCreateRayTracingPipelinesKHR))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyAccelerationStructureKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetAccelerationStructureDeviceAddressKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetAccelerationStructureMemoryRequirementsKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceAccelerationStructureCompatibilityKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetRayTracingCaptureReplayShaderGroupHandlesKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetRayTracingShaderGroupHandlesKHR))
import Vulkan.Dynamic (DeviceCmds(pVkWriteAccelerationStructuresPropertiesKHR))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.FundamentalTypes (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.FundamentalTypes (Flags)
import Vulkan.Core10.Enums.Format (Format)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.IndexType (IndexType)
import Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2 (MemoryRequirements2)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.Core10.Handles (Pipeline)
import Vulkan.Core10.Handles (Pipeline(..))
import Vulkan.Core10.Handles (PipelineCache)
import Vulkan.Core10.Handles (PipelineCache(..))
import Vulkan.Core10.Enums.PipelineCreateFlagBits (PipelineCreateFlags)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_pipeline_creation_feedback (PipelineCreationFeedbackCreateInfoEXT)
import Vulkan.Core10.Handles (PipelineLayout)
import Vulkan.Extensions.VK_KHR_pipeline_library (PipelineLibraryCreateInfoKHR)
import Vulkan.Core10.Pipeline (PipelineShaderStageCreateInfo)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
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.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.FundamentalTypes (Bool32(FALSE))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_BUILD_GEOMETRY_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_GEOMETRY_TYPE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_DEVICE_ADDRESS_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_AABBS_DATA_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_INSTANCES_DATA_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_TRIANGLES_DATA_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_ACCELERATION_STRUCTURE_VERSION_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_BIND_ACCELERATION_STRUCTURE_MEMORY_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_TO_MEMORY_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_COPY_MEMORY_TO_ACCELERATION_STRUCTURE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_FEATURES_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_PROPERTIES_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RAY_TRACING_PIPELINE_CREATE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RAY_TRACING_PIPELINE_INTERFACE_CREATE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_RAY_TRACING_SHADER_GROUP_CREATE_INFO_KHR))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET_ACCELERATION_STRUCTURE_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.APIConstants (pattern UUID_SIZE)
import Vulkan.Extensions.Handles (AccelerationStructureKHR(..))
import Vulkan.Extensions.VK_EXT_debug_report (DebugReportObjectTypeEXT(..))
import Vulkan.Extensions.VK_KHR_pipeline_library (PipelineLibraryCreateInfoKHR(..))
import Vulkan.Core10.APIConstants (SHADER_UNUSED_KHR)
import Vulkan.Core10.APIConstants (pattern SHADER_UNUSED_KHR)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkDestroyAccelerationStructureKHR
  :: FunPtr (Ptr Device_T -> AccelerationStructureKHR -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> AccelerationStructureKHR -> Ptr AllocationCallbacks -> IO ()

-- | vkDestroyAccelerationStructureKHR - Destroy an acceleration structure
-- object
--
-- == Valid Usage
--
-- -   All submitted commands that refer to @accelerationStructure@ /must/
--     have completed execution
--
-- -   If 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @accelerationStructure@ was created, a compatible set
--     of callbacks /must/ be provided here
--
-- -   If no 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @accelerationStructure@ was created, @pAllocator@
--     /must/ be @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @accelerationStructure@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @accelerationStructure@
--     /must/ be a valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   If @accelerationStructure@ is a valid handle, it /must/ have been
--     created, allocated, or retrieved from @device@
--
-- == Host Synchronization
--
-- -   Host access to @accelerationStructure@ /must/ be externally
--     synchronized
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device'
destroyAccelerationStructureKHR :: forall io
                                 . (MonadIO io)
                                => -- | @device@ is the logical device that destroys the buffer.
                                   Device
                                -> -- | @accelerationStructure@ is the acceleration structure to destroy.
                                   AccelerationStructureKHR
                                -> -- | @pAllocator@ controls host memory allocation as described in the
                                   -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                                   -- chapter.
                                   ("allocator" ::: Maybe AllocationCallbacks)
                                -> io ()
destroyAccelerationStructureKHR :: Device
-> AccelerationStructureKHR
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyAccelerationStructureKHR device :: Device
device accelerationStructure :: AccelerationStructureKHR
accelerationStructure allocator :: "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 vkDestroyAccelerationStructureKHRPtr :: FunPtr
  (Ptr Device_T
   -> AccelerationStructureKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyAccelerationStructureKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> AccelerationStructureKHR
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroyAccelerationStructureKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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
   -> AccelerationStructureKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyAccelerationStructureKHRPtr FunPtr
  (Ptr Device_T
   -> AccelerationStructureKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> AccelerationStructureKHR
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> AccelerationStructureKHR
   -> ("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 "" "The function pointer for vkDestroyAccelerationStructureKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyAccelerationStructureKHR' :: Ptr Device_T
-> AccelerationStructureKHR
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyAccelerationStructureKHR' = FunPtr
  (Ptr Device_T
   -> AccelerationStructureKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> Ptr Device_T
-> AccelerationStructureKHR
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyAccelerationStructureKHR FunPtr
  (Ptr Device_T
   -> AccelerationStructureKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyAccelerationStructureKHRPtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    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 j :: 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
$ Ptr Device_T
-> AccelerationStructureKHR
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyAccelerationStructureKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (AccelerationStructureKHR
accelerationStructure) "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" mkVkGetAccelerationStructureMemoryRequirementsKHR
  :: FunPtr (Ptr Device_T -> Ptr AccelerationStructureMemoryRequirementsInfoKHR -> Ptr (SomeStruct MemoryRequirements2) -> IO ()) -> Ptr Device_T -> Ptr AccelerationStructureMemoryRequirementsInfoKHR -> Ptr (SomeStruct MemoryRequirements2) -> IO ()

-- | vkGetAccelerationStructureMemoryRequirementsKHR - Get acceleration
-- structure memory requirements
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'AccelerationStructureMemoryRequirementsInfoKHR',
-- 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_memory_requirements2.MemoryRequirements2'
getAccelerationStructureMemoryRequirementsKHR :: forall a io
                                               . (Extendss MemoryRequirements2 a, PokeChain a, PeekChain a, MonadIO io)
                                              => -- | @device@ is the logical device on which the acceleration structure was
                                                 -- created.
                                                 --
                                                 -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                                 Device
                                              -> -- | @pInfo@ specifies the acceleration structure to get memory requirements
                                                 -- for.
                                                 --
                                                 -- @pInfo@ /must/ be a valid pointer to a valid
                                                 -- 'AccelerationStructureMemoryRequirementsInfoKHR' structure
                                                 AccelerationStructureMemoryRequirementsInfoKHR
                                              -> io (MemoryRequirements2 a)
getAccelerationStructureMemoryRequirementsKHR :: Device
-> AccelerationStructureMemoryRequirementsInfoKHR
-> io (MemoryRequirements2 a)
getAccelerationStructureMemoryRequirementsKHR device :: Device
device info :: AccelerationStructureMemoryRequirementsInfoKHR
info = IO (MemoryRequirements2 a) -> io (MemoryRequirements2 a)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (MemoryRequirements2 a) -> io (MemoryRequirements2 a))
-> (ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a)
    -> IO (MemoryRequirements2 a))
-> ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a)
-> io (MemoryRequirements2 a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a)
-> IO (MemoryRequirements2 a)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a)
 -> io (MemoryRequirements2 a))
-> ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a)
-> io (MemoryRequirements2 a)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetAccelerationStructureMemoryRequirementsKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
   -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
   -> IO ())
vkGetAccelerationStructureMemoryRequirementsKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
      -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
      -> IO ())
pVkGetAccelerationStructureMemoryRequirementsKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT (MemoryRequirements2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (MemoryRequirements2 a) IO ())
-> IO () -> ContT (MemoryRequirements2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
   -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
   -> IO ())
vkGetAccelerationStructureMemoryRequirementsKHRPtr FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
   -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
      -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
   -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
   -> 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 "" "The function pointer for vkGetAccelerationStructureMemoryRequirementsKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetAccelerationStructureMemoryRequirementsKHR' :: Ptr Device_T
-> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
-> IO ()
vkGetAccelerationStructureMemoryRequirementsKHR' = FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
   -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
   -> IO ())
-> Ptr Device_T
-> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
-> IO ()
mkVkGetAccelerationStructureMemoryRequirementsKHR FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
   -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
   -> IO ())
vkGetAccelerationStructureMemoryRequirementsKHRPtr
  "pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
pInfo <- ((("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
  -> IO (MemoryRequirements2 a))
 -> IO (MemoryRequirements2 a))
-> ContT
     (MemoryRequirements2 a)
     IO
     ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
   -> IO (MemoryRequirements2 a))
  -> IO (MemoryRequirements2 a))
 -> ContT
      (MemoryRequirements2 a)
      IO
      ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR))
-> ((("pInfo"
      ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
     -> IO (MemoryRequirements2 a))
    -> IO (MemoryRequirements2 a))
-> ContT
     (MemoryRequirements2 a)
     IO
     ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
forall a b. (a -> b) -> a -> b
$ AccelerationStructureMemoryRequirementsInfoKHR
-> (("pInfo"
     ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
    -> IO (MemoryRequirements2 a))
-> IO (MemoryRequirements2 a)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AccelerationStructureMemoryRequirementsInfoKHR
info)
  Ptr (MemoryRequirements2 a)
pPMemoryRequirements <- ((Ptr (MemoryRequirements2 a) -> IO (MemoryRequirements2 a))
 -> IO (MemoryRequirements2 a))
-> ContT (MemoryRequirements2 a) IO (Ptr (MemoryRequirements2 a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct (MemoryRequirements2 a) =>
(Ptr (MemoryRequirements2 a) -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @(MemoryRequirements2 _))
  IO () -> ContT (MemoryRequirements2 a) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (MemoryRequirements2 a) IO ())
-> IO () -> ContT (MemoryRequirements2 a) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2))
-> IO ()
vkGetAccelerationStructureMemoryRequirementsKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
pInfo (Ptr (MemoryRequirements2 a)
-> "pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (MemoryRequirements2 a)
pPMemoryRequirements))
  MemoryRequirements2 a
pMemoryRequirements <- IO (MemoryRequirements2 a)
-> ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (MemoryRequirements2 a)
 -> ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a))
-> IO (MemoryRequirements2 a)
-> ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a)
forall a b. (a -> b) -> a -> b
$ Ptr (MemoryRequirements2 a) -> IO (MemoryRequirements2 a)
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @(MemoryRequirements2 _) Ptr (MemoryRequirements2 a)
pPMemoryRequirements
  MemoryRequirements2 a
-> ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryRequirements2 a
 -> ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a))
-> MemoryRequirements2 a
-> ContT (MemoryRequirements2 a) IO (MemoryRequirements2 a)
forall a b. (a -> b) -> a -> b
$ (MemoryRequirements2 a
pMemoryRequirements)


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

-- | vkBindAccelerationStructureMemoryKHR - Bind acceleration structure
-- memory
--
-- == 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
--
-- 'BindAccelerationStructureMemoryInfoKHR', 'Vulkan.Core10.Handles.Device'
bindAccelerationStructureMemoryKHR :: forall io
                                    . (MonadIO io)
                                   => -- | @device@ is the logical device that owns the acceleration structures and
                                      -- memory.
                                      --
                                      -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                      Device
                                   -> -- | @pBindInfos@ is a pointer to an array of
                                      -- 'BindAccelerationStructureMemoryInfoKHR' structures describing
                                      -- acceleration structures and memory to bind.
                                      --
                                      -- @pBindInfos@ /must/ be a valid pointer to an array of @bindInfoCount@
                                      -- valid 'BindAccelerationStructureMemoryInfoKHR' structures
                                      ("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR)
                                   -> io ()
bindAccelerationStructureMemoryKHR :: Device
-> ("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR)
-> io ()
bindAccelerationStructureMemoryKHR device :: Device
device bindInfos :: "bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR
bindInfos = 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 vkBindAccelerationStructureMemoryKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
   -> IO Result)
vkBindAccelerationStructureMemoryKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
      -> IO Result)
pVkBindAccelerationStructureMemoryKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
   -> IO Result)
vkBindAccelerationStructureMemoryKHRPtr FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
   -> 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 "" "The function pointer for vkBindAccelerationStructureMemoryKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkBindAccelerationStructureMemoryKHR' :: Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> IO Result
vkBindAccelerationStructureMemoryKHR' = FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
   -> IO Result)
-> Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> IO Result
mkVkBindAccelerationStructureMemoryKHR FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
   -> IO Result)
vkBindAccelerationStructureMemoryKHRPtr
  "pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
pPBindInfos <- ((("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
  -> IO ())
 -> IO ())
-> ContT
     () IO ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR))
-> ((("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
     -> IO ())
    -> IO ())
-> ContT
     () IO ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
    -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @BindAccelerationStructureMemoryInfoKHR ((("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length ("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR
bindInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 56) 8
  (Int -> BindAccelerationStructureMemoryInfoKHR -> ContT () IO ())
-> ("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR)
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: BindAccelerationStructureMemoryInfoKHR
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
$ ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> BindAccelerationStructureMemoryInfoKHR -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
pPBindInfos ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int
-> "pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (56 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr BindAccelerationStructureMemoryInfoKHR) (BindAccelerationStructureMemoryInfoKHR
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
$ ())) ("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR
bindInfos)
  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
$ Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> IO Result
vkBindAccelerationStructureMemoryKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length (("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR)
 -> Int)
-> ("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR)
-> Int
forall a b. (a -> b) -> a -> b
$ ("bindInfos" ::: Vector BindAccelerationStructureMemoryInfoKHR
bindInfos)) :: Word32)) ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
pPBindInfos)
  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" mkVkCmdCopyAccelerationStructureKHR
  :: FunPtr (Ptr CommandBuffer_T -> Ptr (SomeStruct CopyAccelerationStructureInfoKHR) -> IO ()) -> Ptr CommandBuffer_T -> Ptr (SomeStruct CopyAccelerationStructureInfoKHR) -> IO ()

-- | vkCmdCopyAccelerationStructureKHR - Copy an acceleration structure
--
-- == Valid Usage
--
-- -   All 'Vulkan.Extensions.Handles.AccelerationStructureKHR' objects
--     referenced by this command /must/ be bound to device memory
--
-- -   The
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--     structure /must/ not be included in the @pNext@ chain of the
--     'CopyAccelerationStructureInfoKHR' structure
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pInfo@ /must/ be a valid pointer to a valid
--     'CopyAccelerationStructureInfoKHR' structure
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- == 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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Compute                                                                                                               |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'CopyAccelerationStructureInfoKHR'
cmdCopyAccelerationStructureKHR :: forall a io
                                 . (Extendss CopyAccelerationStructureInfoKHR a, PokeChain a, MonadIO io)
                                => -- | @commandBuffer@ is the command buffer into which the command will be
                                   -- recorded.
                                   CommandBuffer
                                -> -- | @pInfo@ is a pointer to a 'CopyAccelerationStructureInfoKHR' structure
                                   -- defining the copy operation.
                                   (CopyAccelerationStructureInfoKHR a)
                                -> io ()
cmdCopyAccelerationStructureKHR :: CommandBuffer -> CopyAccelerationStructureInfoKHR a -> io ()
cmdCopyAccelerationStructureKHR commandBuffer :: CommandBuffer
commandBuffer info :: CopyAccelerationStructureInfoKHR a
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 vkCmdCopyAccelerationStructureKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO ())
vkCmdCopyAccelerationStructureKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
      -> IO ())
pVkCmdCopyAccelerationStructureKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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 (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO ())
vkCmdCopyAccelerationStructureKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> 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 "" "The function pointer for vkCmdCopyAccelerationStructureKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyAccelerationStructureKHR' :: Ptr CommandBuffer_T
-> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
-> IO ()
vkCmdCopyAccelerationStructureKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
-> IO ()
mkVkCmdCopyAccelerationStructureKHR FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO ())
vkCmdCopyAccelerationStructureKHRPtr
  Ptr (CopyAccelerationStructureInfoKHR a)
pInfo <- ((Ptr (CopyAccelerationStructureInfoKHR a) -> IO ()) -> IO ())
-> ContT () IO (Ptr (CopyAccelerationStructureInfoKHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (CopyAccelerationStructureInfoKHR a) -> IO ()) -> IO ())
 -> ContT () IO (Ptr (CopyAccelerationStructureInfoKHR a)))
-> ((Ptr (CopyAccelerationStructureInfoKHR a) -> IO ()) -> IO ())
-> ContT () IO (Ptr (CopyAccelerationStructureInfoKHR a))
forall a b. (a -> b) -> a -> b
$ CopyAccelerationStructureInfoKHR a
-> (Ptr (CopyAccelerationStructureInfoKHR a) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyAccelerationStructureInfoKHR a
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
$ Ptr CommandBuffer_T
-> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
-> IO ()
vkCmdCopyAccelerationStructureKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Ptr (CopyAccelerationStructureInfoKHR a)
-> "pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (CopyAccelerationStructureInfoKHR a)
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" mkVkCopyAccelerationStructureKHR
  :: FunPtr (Ptr Device_T -> Ptr (SomeStruct CopyAccelerationStructureInfoKHR) -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct CopyAccelerationStructureInfoKHR) -> IO Result

-- | vkCopyAccelerationStructureKHR - Copy an acceleration structure on the
-- host
--
-- = Parameters
--
-- This command fulfills the same task as 'cmdCopyAccelerationStructureKHR'
-- but executed by the host.
--
-- = Description
--
-- -   @device@ is the device which owns the acceleration structures.
--
-- -   @pInfo@ is a pointer to a 'CopyAccelerationStructureInfoKHR'
--     structure defining the copy operation.
--
-- If the
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
-- structure is included in the @pNext@ chain of the
-- 'CopyAccelerationStructureInfoKHR' structure, the operation of this
-- command is /deferred/, as defined in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#deferred-host-operations Deferred Host Operations>
-- chapter.
--
-- == Valid Usage
--
-- -   All 'Vulkan.Extensions.Handles.AccelerationStructureKHR' objects
--     referenced by this command /must/ be bound to host-visible memory
--
-- -   the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing-hostascmds ::rayTracingHostAccelerationStructureCommands>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pInfo@ /must/ be a valid pointer to a valid
--     'CopyAccelerationStructureInfoKHR' structure
--
-- == 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
--
-- 'CopyAccelerationStructureInfoKHR', 'Vulkan.Core10.Handles.Device'
copyAccelerationStructureKHR :: forall a io
                              . (Extendss CopyAccelerationStructureInfoKHR a, PokeChain a, MonadIO io)
                             => -- No documentation found for Nested "vkCopyAccelerationStructureKHR" "device"
                                Device
                             -> -- No documentation found for Nested "vkCopyAccelerationStructureKHR" "pInfo"
                                (CopyAccelerationStructureInfoKHR a)
                             -> io (Result)
copyAccelerationStructureKHR :: Device -> CopyAccelerationStructureInfoKHR a -> io Result
copyAccelerationStructureKHR device :: Device
device info :: CopyAccelerationStructureInfoKHR a
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 vkCopyAccelerationStructureKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO Result)
vkCopyAccelerationStructureKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
      -> IO Result)
pVkCopyAccelerationStructureKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO Result)
vkCopyAccelerationStructureKHRPtr FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> 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 "" "The function pointer for vkCopyAccelerationStructureKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCopyAccelerationStructureKHR' :: Ptr Device_T
-> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
-> IO Result
vkCopyAccelerationStructureKHR' = FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO Result)
-> Ptr Device_T
-> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
-> IO Result
mkVkCopyAccelerationStructureKHR FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
   -> IO Result)
vkCopyAccelerationStructureKHRPtr
  Ptr (CopyAccelerationStructureInfoKHR a)
pInfo <- ((Ptr (CopyAccelerationStructureInfoKHR a) -> IO Result)
 -> IO Result)
-> ContT Result IO (Ptr (CopyAccelerationStructureInfoKHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (CopyAccelerationStructureInfoKHR a) -> IO Result)
  -> IO Result)
 -> ContT Result IO (Ptr (CopyAccelerationStructureInfoKHR a)))
-> ((Ptr (CopyAccelerationStructureInfoKHR a) -> IO Result)
    -> IO Result)
-> ContT Result IO (Ptr (CopyAccelerationStructureInfoKHR a))
forall a b. (a -> b) -> a -> b
$ CopyAccelerationStructureInfoKHR a
-> (Ptr (CopyAccelerationStructureInfoKHR a) -> IO Result)
-> IO Result
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyAccelerationStructureInfoKHR a
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
$ Ptr Device_T
-> ("pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR))
-> IO Result
vkCopyAccelerationStructureKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (CopyAccelerationStructureInfoKHR a)
-> "pInfo" ::: Ptr (SomeStruct CopyAccelerationStructureInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (CopyAccelerationStructureInfoKHR a)
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" mkVkCmdCopyAccelerationStructureToMemoryKHR
  :: FunPtr (Ptr CommandBuffer_T -> Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR) -> IO ()) -> Ptr CommandBuffer_T -> Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR) -> IO ()

-- | vkCmdCopyAccelerationStructureToMemoryKHR - Copy an acceleration
-- structure to device memory
--
-- = Parameters
--
-- This command produces the same results as
-- 'copyAccelerationStructureToMemoryKHR', 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 'cmdCopyMemoryToAccelerationStructureKHR' or
-- 'copyMemoryToAccelerationStructureKHR'.
--
-- = Description
--
-- -   @commandBuffer@ is the command buffer into which the command will be
--     recorded.
--
-- -   @pInfo@ is an a pointer to a
--     'CopyAccelerationStructureToMemoryInfoKHR' structure defining the
--     copy operation.
--
-- 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
--     'getDeviceAccelerationStructureCompatibilityKHR'
--
-- -   A 64-bit integer of the total size matching the value queried using
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR'
--
-- -   A 64-bit integer of the deserialized size to be passed in to
--     'AccelerationStructureCreateInfoKHR'::@compactedSize@
--
-- -   A 64-bit integer of the count of the number of acceleration
--     structure handles following. This will be zero for a bottom-level
--     acceleration structure.
--
-- The corresponding handles matching the values returned by
-- 'getAccelerationStructureDeviceAddressKHR' or
-- 'Vulkan.Extensions.VK_NV_ray_tracing.getAccelerationStructureHandleNV'
-- are tightly packed in the buffer following the count. The application is
-- expected to store a mapping between those handles and the original
-- application-generated bottom-level acceleration structures to provide
-- when deserializing.
--
-- == Valid Usage
--
-- -   All 'DeviceOrHostAddressConstKHR' referenced by this command /must/
--     contain valid device addresses for a buffer bound to device memory.
--     If the buffer is non-sparse then it /must/ be bound completely and
--     contiguously to a single VkDeviceMemory object
--
-- -   All 'Vulkan.Extensions.Handles.AccelerationStructureKHR' objects
--     referenced by this command /must/ be bound to device memory
--
-- -   The
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--     structure /must/ not be included in the @pNext@ chain of the
--     'CopyAccelerationStructureToMemoryInfoKHR' structure
--
-- -   @mode@ /must/ be 'COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pInfo@ /must/ be a valid pointer to a valid
--     'CopyAccelerationStructureToMemoryInfoKHR' structure
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- == 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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Compute                                                                                                               |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'CopyAccelerationStructureToMemoryInfoKHR'
cmdCopyAccelerationStructureToMemoryKHR :: forall a io
                                         . (Extendss CopyAccelerationStructureToMemoryInfoKHR a, PokeChain a, MonadIO io)
                                        => -- No documentation found for Nested "vkCmdCopyAccelerationStructureToMemoryKHR" "commandBuffer"
                                           CommandBuffer
                                        -> -- No documentation found for Nested "vkCmdCopyAccelerationStructureToMemoryKHR" "pInfo"
                                           (CopyAccelerationStructureToMemoryInfoKHR a)
                                        -> io ()
cmdCopyAccelerationStructureToMemoryKHR :: CommandBuffer
-> CopyAccelerationStructureToMemoryInfoKHR a -> io ()
cmdCopyAccelerationStructureToMemoryKHR commandBuffer :: CommandBuffer
commandBuffer info :: CopyAccelerationStructureToMemoryInfoKHR a
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 vkCmdCopyAccelerationStructureToMemoryKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO ())
vkCmdCopyAccelerationStructureToMemoryKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfo"
          ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
      -> IO ())
pVkCmdCopyAccelerationStructureToMemoryKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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 (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO ())
vkCmdCopyAccelerationStructureToMemoryKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfo"
          ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> 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 "" "The function pointer for vkCmdCopyAccelerationStructureToMemoryKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyAccelerationStructureToMemoryKHR' :: Ptr CommandBuffer_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
-> IO ()
vkCmdCopyAccelerationStructureToMemoryKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
-> IO ()
mkVkCmdCopyAccelerationStructureToMemoryKHR FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO ())
vkCmdCopyAccelerationStructureToMemoryKHRPtr
  Ptr (CopyAccelerationStructureToMemoryInfoKHR a)
pInfo <- ((Ptr (CopyAccelerationStructureToMemoryInfoKHR a) -> IO ())
 -> IO ())
-> ContT () IO (Ptr (CopyAccelerationStructureToMemoryInfoKHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (CopyAccelerationStructureToMemoryInfoKHR a) -> IO ())
  -> IO ())
 -> ContT () IO (Ptr (CopyAccelerationStructureToMemoryInfoKHR a)))
-> ((Ptr (CopyAccelerationStructureToMemoryInfoKHR a) -> IO ())
    -> IO ())
-> ContT () IO (Ptr (CopyAccelerationStructureToMemoryInfoKHR a))
forall a b. (a -> b) -> a -> b
$ CopyAccelerationStructureToMemoryInfoKHR a
-> (Ptr (CopyAccelerationStructureToMemoryInfoKHR a) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyAccelerationStructureToMemoryInfoKHR a
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
$ Ptr CommandBuffer_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
-> IO ()
vkCmdCopyAccelerationStructureToMemoryKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Ptr (CopyAccelerationStructureToMemoryInfoKHR a)
-> "pInfo"
   ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (CopyAccelerationStructureToMemoryInfoKHR a)
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" mkVkCopyAccelerationStructureToMemoryKHR
  :: FunPtr (Ptr Device_T -> Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR) -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR) -> IO Result

-- | vkCopyAccelerationStructureToMemoryKHR - Serialize an acceleration
-- structure on the host
--
-- = Parameters
--
-- This command fulfills the same task as
-- 'cmdCopyAccelerationStructureToMemoryKHR' but executed by the host.
--
-- = Description
--
-- This command produces the same results as
-- 'cmdCopyAccelerationStructureToMemoryKHR', 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
-- 'cmdCopyMemoryToAccelerationStructureKHR' or
-- 'copyMemoryToAccelerationStructureKHR'.
--
-- -   @device@ is the device which owns @pInfo->src@.
--
-- -   @pInfo@ is a pointer to a 'CopyAccelerationStructureToMemoryInfoKHR'
--     structure defining the copy operation.
--
-- If the
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
-- structure is included in the @pNext@ chain of the
-- 'CopyAccelerationStructureToMemoryInfoKHR' structure, the operation of
-- this command is /deferred/, as defined in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#deferred-host-operations>
-- chapter.
--
-- == Valid Usage
--
-- -   All 'Vulkan.Extensions.Handles.AccelerationStructureKHR' objects
--     referenced by this command /must/ be bound to host-visible memory
--
-- -   All 'DeviceOrHostAddressKHR' referenced by this command /must/
--     contain valid host pointers
--
-- -   the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing-hostascmds ::rayTracingHostAccelerationStructureCommands>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pInfo@ /must/ be a valid pointer to a valid
--     'CopyAccelerationStructureToMemoryInfoKHR' structure
--
-- == 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
--
-- 'CopyAccelerationStructureToMemoryInfoKHR',
-- 'Vulkan.Core10.Handles.Device'
copyAccelerationStructureToMemoryKHR :: forall a io
                                      . (Extendss CopyAccelerationStructureToMemoryInfoKHR a, PokeChain a, MonadIO io)
                                     => -- No documentation found for Nested "vkCopyAccelerationStructureToMemoryKHR" "device"
                                        Device
                                     -> -- No documentation found for Nested "vkCopyAccelerationStructureToMemoryKHR" "pInfo"
                                        (CopyAccelerationStructureToMemoryInfoKHR a)
                                     -> io (Result)
copyAccelerationStructureToMemoryKHR :: Device -> CopyAccelerationStructureToMemoryInfoKHR a -> io Result
copyAccelerationStructureToMemoryKHR device :: Device
device info :: CopyAccelerationStructureToMemoryInfoKHR a
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 vkCopyAccelerationStructureToMemoryKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO Result)
vkCopyAccelerationStructureToMemoryKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pInfo"
          ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
      -> IO Result)
pVkCopyAccelerationStructureToMemoryKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO Result)
vkCopyAccelerationStructureToMemoryKHRPtr FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pInfo"
          ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> 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 "" "The function pointer for vkCopyAccelerationStructureToMemoryKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCopyAccelerationStructureToMemoryKHR' :: Ptr Device_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
-> IO Result
vkCopyAccelerationStructureToMemoryKHR' = FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO Result)
-> Ptr Device_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
-> IO Result
mkVkCopyAccelerationStructureToMemoryKHR FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
   -> IO Result)
vkCopyAccelerationStructureToMemoryKHRPtr
  Ptr (CopyAccelerationStructureToMemoryInfoKHR a)
pInfo <- ((Ptr (CopyAccelerationStructureToMemoryInfoKHR a) -> IO Result)
 -> IO Result)
-> ContT
     Result IO (Ptr (CopyAccelerationStructureToMemoryInfoKHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (CopyAccelerationStructureToMemoryInfoKHR a) -> IO Result)
  -> IO Result)
 -> ContT
      Result IO (Ptr (CopyAccelerationStructureToMemoryInfoKHR a)))
-> ((Ptr (CopyAccelerationStructureToMemoryInfoKHR a) -> IO Result)
    -> IO Result)
-> ContT
     Result IO (Ptr (CopyAccelerationStructureToMemoryInfoKHR a))
forall a b. (a -> b) -> a -> b
$ CopyAccelerationStructureToMemoryInfoKHR a
-> (Ptr (CopyAccelerationStructureToMemoryInfoKHR a) -> IO Result)
-> IO Result
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyAccelerationStructureToMemoryInfoKHR a
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
$ Ptr Device_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR))
-> IO Result
vkCopyAccelerationStructureToMemoryKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (CopyAccelerationStructureToMemoryInfoKHR a)
-> "pInfo"
   ::: Ptr (SomeStruct CopyAccelerationStructureToMemoryInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (CopyAccelerationStructureToMemoryInfoKHR a)
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" mkVkCmdCopyMemoryToAccelerationStructureKHR
  :: FunPtr (Ptr CommandBuffer_T -> Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR) -> IO ()) -> Ptr CommandBuffer_T -> Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR) -> IO ()

-- | vkCmdCopyMemoryToAccelerationStructureKHR - Copy device memory to an
-- acceleration structure
--
-- = Parameters
--
-- This command can accept acceleration structures produced by either
-- 'cmdCopyAccelerationStructureToMemoryKHR' or
-- 'copyAccelerationStructureToMemoryKHR'.
--
-- = Description
--
-- -   @commandBuffer@ is the command buffer into which the command will be
--     recorded.
--
-- -   @pInfo@ is a pointer to a 'CopyMemoryToAccelerationStructureInfoKHR'
--     structure defining the copy operation.
--
-- The structure provided as input to deserialize is as described in
-- 'cmdCopyAccelerationStructureToMemoryKHR', with any acceleration
-- structure handles filled in with the newly-queried handles to bottom
-- level acceleration structures created before deserialization. These do
-- not need to be built at deserialize time, but /must/ be created.
--
-- == Valid Usage
--
-- -   All 'DeviceOrHostAddressKHR' referenced by this command /must/
--     contain valid device addresses for a buffer bound to device memory.
--     If the buffer is non-sparse then it /must/ be bound completely and
--     contiguously to a single VkDeviceMemory object
--
-- -   All 'Vulkan.Extensions.Handles.AccelerationStructureKHR' objects
--     referenced by this command /must/ be bound to device memory
--
-- -   The
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--     structure /must/ not be included in the @pNext@ chain of the
--     'CopyMemoryToAccelerationStructureInfoKHR' structure
--
-- -   @mode@ /must/ be 'COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR'
--
-- -   The data in @pInfo->src@ /must/ have a format compatible with the
--     destination physical device as returned by
--     'getDeviceAccelerationStructureCompatibilityKHR'
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pInfo@ /must/ be a valid pointer to a valid
--     'CopyMemoryToAccelerationStructureInfoKHR' structure
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- == 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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Compute                                                                                                               |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'CopyMemoryToAccelerationStructureInfoKHR'
cmdCopyMemoryToAccelerationStructureKHR :: forall a io
                                         . (Extendss CopyMemoryToAccelerationStructureInfoKHR a, PokeChain a, MonadIO io)
                                        => -- No documentation found for Nested "vkCmdCopyMemoryToAccelerationStructureKHR" "commandBuffer"
                                           CommandBuffer
                                        -> -- No documentation found for Nested "vkCmdCopyMemoryToAccelerationStructureKHR" "pInfo"
                                           (CopyMemoryToAccelerationStructureInfoKHR a)
                                        -> io ()
cmdCopyMemoryToAccelerationStructureKHR :: CommandBuffer
-> CopyMemoryToAccelerationStructureInfoKHR a -> io ()
cmdCopyMemoryToAccelerationStructureKHR commandBuffer :: CommandBuffer
commandBuffer info :: CopyMemoryToAccelerationStructureInfoKHR a
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 vkCmdCopyMemoryToAccelerationStructureKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO ())
vkCmdCopyMemoryToAccelerationStructureKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfo"
          ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
      -> IO ())
pVkCmdCopyMemoryToAccelerationStructureKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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 (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO ())
vkCmdCopyMemoryToAccelerationStructureKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfo"
          ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> 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 "" "The function pointer for vkCmdCopyMemoryToAccelerationStructureKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdCopyMemoryToAccelerationStructureKHR' :: Ptr CommandBuffer_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
-> IO ()
vkCmdCopyMemoryToAccelerationStructureKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
-> IO ()
mkVkCmdCopyMemoryToAccelerationStructureKHR FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO ())
vkCmdCopyMemoryToAccelerationStructureKHRPtr
  Ptr (CopyMemoryToAccelerationStructureInfoKHR a)
pInfo <- ((Ptr (CopyMemoryToAccelerationStructureInfoKHR a) -> IO ())
 -> IO ())
-> ContT () IO (Ptr (CopyMemoryToAccelerationStructureInfoKHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (CopyMemoryToAccelerationStructureInfoKHR a) -> IO ())
  -> IO ())
 -> ContT () IO (Ptr (CopyMemoryToAccelerationStructureInfoKHR a)))
-> ((Ptr (CopyMemoryToAccelerationStructureInfoKHR a) -> IO ())
    -> IO ())
-> ContT () IO (Ptr (CopyMemoryToAccelerationStructureInfoKHR a))
forall a b. (a -> b) -> a -> b
$ CopyMemoryToAccelerationStructureInfoKHR a
-> (Ptr (CopyMemoryToAccelerationStructureInfoKHR a) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyMemoryToAccelerationStructureInfoKHR a
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
$ Ptr CommandBuffer_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
-> IO ()
vkCmdCopyMemoryToAccelerationStructureKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Ptr (CopyMemoryToAccelerationStructureInfoKHR a)
-> "pInfo"
   ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (CopyMemoryToAccelerationStructureInfoKHR a)
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" mkVkCopyMemoryToAccelerationStructureKHR
  :: FunPtr (Ptr Device_T -> Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR) -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR) -> IO Result

-- | vkCopyMemoryToAccelerationStructureKHR - Deserialize an acceleration
-- structure on the host
--
-- = Parameters
--
-- This command fulfills the same task as
-- 'cmdCopyMemoryToAccelerationStructureKHR' but is executed by the host.
--
-- = Description
--
-- This command can accept acceleration structures produced by either
-- 'cmdCopyAccelerationStructureToMemoryKHR' or
-- 'copyAccelerationStructureToMemoryKHR'.
--
-- -   @device@ is the device which owns @pInfo->dst@.
--
-- -   @pInfo@ is a pointer to a 'CopyMemoryToAccelerationStructureInfoKHR'
--     structure defining the copy operation.
--
-- If the
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
-- structure is included in the @pNext@ chain of the
-- 'CopyMemoryToAccelerationStructureInfoKHR' structure, the operation of
-- this command is /deferred/, as defined in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#deferred-host-operations Deferred Host Operations>
-- chapter.
--
-- == Valid Usage
--
-- -   All 'Vulkan.Extensions.Handles.AccelerationStructureKHR' objects
--     referenced by this command /must/ be bound to host-visible memory
--
-- -   All 'DeviceOrHostAddressConstKHR' referenced by this command /must/
--     contain valid host pointers
--
-- -   the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing-hostascmds ::rayTracingHostAccelerationStructureCommands>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pInfo@ /must/ be a valid pointer to a valid
--     'CopyMemoryToAccelerationStructureInfoKHR' structure
--
-- == 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
--
-- 'CopyMemoryToAccelerationStructureInfoKHR',
-- 'Vulkan.Core10.Handles.Device'
copyMemoryToAccelerationStructureKHR :: forall a io
                                      . (Extendss CopyMemoryToAccelerationStructureInfoKHR a, PokeChain a, MonadIO io)
                                     => -- No documentation found for Nested "vkCopyMemoryToAccelerationStructureKHR" "device"
                                        Device
                                     -> -- No documentation found for Nested "vkCopyMemoryToAccelerationStructureKHR" "pInfo"
                                        (CopyMemoryToAccelerationStructureInfoKHR a)
                                     -> io (Result)
copyMemoryToAccelerationStructureKHR :: Device -> CopyMemoryToAccelerationStructureInfoKHR a -> io Result
copyMemoryToAccelerationStructureKHR device :: Device
device info :: CopyMemoryToAccelerationStructureInfoKHR a
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 vkCopyMemoryToAccelerationStructureKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO Result)
vkCopyMemoryToAccelerationStructureKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pInfo"
          ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
      -> IO Result)
pVkCopyMemoryToAccelerationStructureKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO Result)
vkCopyMemoryToAccelerationStructureKHRPtr FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pInfo"
          ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> 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 "" "The function pointer for vkCopyMemoryToAccelerationStructureKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCopyMemoryToAccelerationStructureKHR' :: Ptr Device_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
-> IO Result
vkCopyMemoryToAccelerationStructureKHR' = FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO Result)
-> Ptr Device_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
-> IO Result
mkVkCopyMemoryToAccelerationStructureKHR FunPtr
  (Ptr Device_T
   -> ("pInfo"
       ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
   -> IO Result)
vkCopyMemoryToAccelerationStructureKHRPtr
  Ptr (CopyMemoryToAccelerationStructureInfoKHR a)
pInfo <- ((Ptr (CopyMemoryToAccelerationStructureInfoKHR a) -> IO Result)
 -> IO Result)
-> ContT
     Result IO (Ptr (CopyMemoryToAccelerationStructureInfoKHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (CopyMemoryToAccelerationStructureInfoKHR a) -> IO Result)
  -> IO Result)
 -> ContT
      Result IO (Ptr (CopyMemoryToAccelerationStructureInfoKHR a)))
-> ((Ptr (CopyMemoryToAccelerationStructureInfoKHR a) -> IO Result)
    -> IO Result)
-> ContT
     Result IO (Ptr (CopyMemoryToAccelerationStructureInfoKHR a))
forall a b. (a -> b) -> a -> b
$ CopyMemoryToAccelerationStructureInfoKHR a
-> (Ptr (CopyMemoryToAccelerationStructureInfoKHR a) -> IO Result)
-> IO Result
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (CopyMemoryToAccelerationStructureInfoKHR a
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
$ Ptr Device_T
-> ("pInfo"
    ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR))
-> IO Result
vkCopyMemoryToAccelerationStructureKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (CopyMemoryToAccelerationStructureInfoKHR a)
-> "pInfo"
   ::: Ptr (SomeStruct CopyMemoryToAccelerationStructureInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (CopyMemoryToAccelerationStructureInfoKHR a)
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" mkVkCmdWriteAccelerationStructuresPropertiesKHR
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr AccelerationStructureKHR -> QueryType -> QueryPool -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr AccelerationStructureKHR -> QueryType -> QueryPool -> Word32 -> IO ()

-- | vkCmdWriteAccelerationStructuresPropertiesKHR - Write acceleration
-- structure result parameters to query results.
--
-- == Valid Usage
--
-- -   @queryPool@ /must/ have been created with a @queryType@ matching
--     @queryType@
--
-- -   The queries identified by @queryPool@ and @firstQuery@ /must/ be
--     /unavailable/
--
-- -   All acceleration structures in @accelerationStructures@ /must/ have
--     been built with
--     'BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR' if
--     @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR'
--
-- -   @queryType@ /must/ be
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR'
--     or
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pAccelerationStructures@ /must/ be a valid pointer to an array of
--     @accelerationStructureCount@ valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handles
--
-- -   @queryType@ /must/ be a valid
--     'Vulkan.Core10.Enums.QueryType.QueryType' value
--
-- -   @queryPool@ /must/ be a valid 'Vulkan.Core10.Handles.QueryPool'
--     handle
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @accelerationStructureCount@ /must/ be greater than @0@
--
-- -   Each of @commandBuffer@, @queryPool@, and the elements of
--     @pAccelerationStructures@ /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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Compute                                                                                                               |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Handles.QueryPool',
-- 'Vulkan.Core10.Enums.QueryType.QueryType'
cmdWriteAccelerationStructuresPropertiesKHR :: forall io
                                             . (MonadIO io)
                                            => -- | @commandBuffer@ is the command buffer into which the command will be
                                               -- recorded.
                                               CommandBuffer
                                            -> -- | @pAccelerationStructures@ is a pointer to an array of existing
                                               -- previously built acceleration structures.
                                               ("accelerationStructures" ::: Vector AccelerationStructureKHR)
                                            -> -- | @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 @accelerationStructureCount@ number of results.
                                               ("firstQuery" ::: Word32)
                                            -> io ()
cmdWriteAccelerationStructuresPropertiesKHR :: CommandBuffer
-> ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> QueryType
-> QueryPool
-> ("bindInfoCount" ::: Word32)
-> io ()
cmdWriteAccelerationStructuresPropertiesKHR commandBuffer :: CommandBuffer
commandBuffer accelerationStructures :: "accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures queryType :: QueryType
queryType queryPool :: QueryPool
queryPool firstQuery :: "bindInfoCount" ::: Word32
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 vkCmdWriteAccelerationStructuresPropertiesKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> QueryPool
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
vkCmdWriteAccelerationStructuresPropertiesKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
      -> QueryType
      -> QueryPool
      -> ("bindInfoCount" ::: Word32)
      -> IO ())
pVkCmdWriteAccelerationStructuresPropertiesKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> QueryPool
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
vkCmdWriteAccelerationStructuresPropertiesKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> QueryPool
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
      -> QueryType
      -> QueryPool
      -> ("bindInfoCount" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> QueryPool
   -> ("bindInfoCount" ::: Word32)
   -> 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 "" "The function pointer for vkCmdWriteAccelerationStructuresPropertiesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdWriteAccelerationStructuresPropertiesKHR' :: Ptr CommandBuffer_T
-> ("bindInfoCount" ::: Word32)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> QueryType
-> QueryPool
-> ("bindInfoCount" ::: Word32)
-> IO ()
vkCmdWriteAccelerationStructuresPropertiesKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> QueryPool
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("bindInfoCount" ::: Word32)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> QueryType
-> QueryPool
-> ("bindInfoCount" ::: Word32)
-> IO ()
mkVkCmdWriteAccelerationStructuresPropertiesKHR FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> QueryPool
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
vkCmdWriteAccelerationStructuresPropertiesKHRPtr
  "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures <- ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
  -> IO ())
 -> IO ())
-> ContT
     () IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO ())
  -> IO ())
 -> ContT
      () IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR))
-> ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
     -> IO ())
    -> IO ())
-> ContT
     () IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
    -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AccelerationStructureKHR ((("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length ("accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 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 -> AccelerationStructureKHR -> IO ())
-> ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AccelerationStructureKHR
e -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AccelerationStructureKHR) (AccelerationStructureKHR
e)) ("accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures)
  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
$ Ptr CommandBuffer_T
-> ("bindInfoCount" ::: Word32)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> QueryType
-> QueryPool
-> ("bindInfoCount" ::: Word32)
-> IO ()
vkCmdWriteAccelerationStructuresPropertiesKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length (("accelerationStructures" ::: Vector AccelerationStructureKHR)
 -> Int)
-> ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> Int
forall a b. (a -> b) -> a -> b
$ ("accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures)) :: Word32)) ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures) (QueryType
queryType) (QueryPool
queryPool) ("bindInfoCount" ::: Word32
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" mkVkWriteAccelerationStructuresPropertiesKHR
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr AccelerationStructureKHR -> QueryType -> CSize -> Ptr () -> CSize -> IO Result) -> Ptr Device_T -> Word32 -> Ptr AccelerationStructureKHR -> QueryType -> CSize -> Ptr () -> CSize -> IO Result

-- | vkWriteAccelerationStructuresPropertiesKHR - Query acceleration
-- structure meta-data on the host
--
-- = Parameters
--
-- This command fulfills the same task as
-- 'cmdWriteAccelerationStructuresPropertiesKHR' but executed by the host.
--
-- = Description
--
-- -   @device@ is the device which owns the acceleration structures in
--     @pAccelerationStructures@.
--
-- -   @accelerationStructureCount@ is the count of acceleration structures
--     for which to query the property.
--
-- -   @pAccelerationStructures@ points to an array of existing previously
--     built acceleration structures.
--
-- -   @queryType@ is a 'Vulkan.Core10.Enums.QueryType.QueryType' value
--     specifying the property to be queried.
--
-- -   @dataSize@ is the size in bytes of the buffer pointed to by @pData@.
--
-- -   @pData@ is a pointer to a user-allocated buffer where the results
--     will be written.
--
-- -   @stride@ is the stride in bytes between results for individual
--     queries within @pData@.
--
-- == Valid Usage
--
-- -   If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR',
--     then @stride@ /must/ be a multiple of the size of
--     'Vulkan.Core10.FundamentalTypes.DeviceSize'
--
-- -   If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR',
--     then @data@ /must/ point to a
--     'Vulkan.Core10.FundamentalTypes.DeviceSize'
--
-- -   If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR',
--     then @stride@ /must/ be a multiple of the size of
--     'Vulkan.Core10.FundamentalTypes.DeviceSize'
--
-- -   If @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR',
--     then @data@ /must/ point to a
--     'Vulkan.Core10.FundamentalTypes.DeviceSize'
--
-- -   @dataSize@ /must/ be greater than or equal to
--     @accelerationStructureCount@*@stride@
--
-- -   The acceleration structures referenced by @pAccelerationStructures@
--     /must/ be bound to host-visible memory
--
-- -   All acceleration structures in @accelerationStructures@ /must/ have
--     been built with
--     'BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR' if
--     @queryType@ is
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR'
--
-- -   @queryType@ /must/ be
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_COMPACTED_SIZE_KHR'
--     or
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR'
--
-- -   the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing-hostascmds ::rayTracingHostAccelerationStructureCommands>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pAccelerationStructures@ /must/ be a valid pointer to an array of
--     @accelerationStructureCount@ valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handles
--
-- -   @queryType@ /must/ be a valid
--     'Vulkan.Core10.Enums.QueryType.QueryType' value
--
-- -   @pData@ /must/ be a valid pointer to an array of @dataSize@ bytes
--
-- -   @accelerationStructureCount@ /must/ be greater than @0@
--
-- -   @dataSize@ /must/ be greater than @0@
--
-- -   Each element of @pAccelerationStructures@ /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
--
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Core10.Enums.QueryType.QueryType'
writeAccelerationStructuresPropertiesKHR :: forall io
                                          . (MonadIO io)
                                         => -- No documentation found for Nested "vkWriteAccelerationStructuresPropertiesKHR" "device"
                                            Device
                                         -> -- No documentation found for Nested "vkWriteAccelerationStructuresPropertiesKHR" "pAccelerationStructures"
                                            ("accelerationStructures" ::: Vector AccelerationStructureKHR)
                                         -> -- No documentation found for Nested "vkWriteAccelerationStructuresPropertiesKHR" "queryType"
                                            QueryType
                                         -> -- No documentation found for Nested "vkWriteAccelerationStructuresPropertiesKHR" "dataSize"
                                            ("dataSize" ::: Word64)
                                         -> -- No documentation found for Nested "vkWriteAccelerationStructuresPropertiesKHR" "pData"
                                            ("data" ::: Ptr ())
                                         -> -- No documentation found for Nested "vkWriteAccelerationStructuresPropertiesKHR" "stride"
                                            ("stride" ::: Word64)
                                         -> io ()
writeAccelerationStructuresPropertiesKHR :: Device
-> ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> QueryType
-> ("dataSize" ::: Word64)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: Word64)
-> io ()
writeAccelerationStructuresPropertiesKHR device :: Device
device accelerationStructures :: "accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures queryType :: QueryType
queryType dataSize :: "dataSize" ::: Word64
dataSize data' :: "data" ::: Ptr ()
data' stride :: "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 vkWriteAccelerationStructuresPropertiesKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
vkWriteAccelerationStructuresPropertiesKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
      -> QueryType
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> ("dataSize" ::: CSize)
      -> IO Result)
pVkWriteAccelerationStructuresPropertiesKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
vkWriteAccelerationStructuresPropertiesKHRPtr FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
      -> QueryType
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> ("dataSize" ::: CSize)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> 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 "" "The function pointer for vkWriteAccelerationStructuresPropertiesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkWriteAccelerationStructuresPropertiesKHR' :: Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> QueryType
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: CSize)
-> IO Result
vkWriteAccelerationStructuresPropertiesKHR' = FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
-> Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> QueryType
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: CSize)
-> IO Result
mkVkWriteAccelerationStructuresPropertiesKHR FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> QueryType
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> ("dataSize" ::: CSize)
   -> IO Result)
vkWriteAccelerationStructuresPropertiesKHRPtr
  "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures <- ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
  -> IO ())
 -> IO ())
-> ContT
     () IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO ())
  -> IO ())
 -> ContT
      () IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR))
-> ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
     -> IO ())
    -> IO ())
-> ContT
     () IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
    -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AccelerationStructureKHR ((("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length ("accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 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 -> AccelerationStructureKHR -> IO ())
-> ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AccelerationStructureKHR
e -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AccelerationStructureKHR) (AccelerationStructureKHR
e)) ("accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures)
  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
$ Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> QueryType
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> ("dataSize" ::: CSize)
-> IO Result
vkWriteAccelerationStructuresPropertiesKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length (("accelerationStructures" ::: Vector AccelerationStructureKHR)
 -> Int)
-> ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> Int
forall a b. (a -> b) -> a -> b
$ ("accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures)) :: Word32)) ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures) (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" mkVkCmdTraceRaysKHR
  :: FunPtr (Ptr CommandBuffer_T -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Word32 -> Word32 -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Word32 -> Word32 -> Word32 -> IO ()

-- | vkCmdTraceRaysKHR - Initialize a ray tracing dispatch
--
-- = Description
--
-- When the command is executed, a ray generation group of @width@ ×
-- @height@ × @depth@ rays is assembled.
--
-- == Valid Usage
--
-- -   If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or
--     @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and
--     @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is
--     used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of
--     this command, then the image view’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features>
--     /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is accessed using atomic
--     operations as a result of this command, then the image view’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features>
--     /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT'
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is sampled with
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result
--     of this command, then the image view’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features>
--     /must/ contain
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT'
--
-- -   Any 'Vulkan.Core10.Handles.ImageView' being sampled with
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result
--     of this command /must/ have a
--     'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that
--     supports cubic filtering, as specified by
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@
--     returned by
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2'
--
-- -   Any 'Vulkan.Core10.Handles.ImageView' being sampled with
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' with a
--     reduction mode of either
--     'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN'
--     or
--     'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX'
--     as a result of this command /must/ have a
--     'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that
--     supports cubic filtering together with minmax filtering, as
--     specified by
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@
--     returned by
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2'
--
-- -   Any 'Vulkan.Core10.Handles.Image' created with a
--     'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV'
--     sampled as a result of this command /must/ only be sampled using a
--     'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of
--     'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE'
--
-- -   For each set /n/ that is statically used by the
--     'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point
--     used by this command, a descriptor set /must/ have been bound to /n/
--     at the same pipeline bind point, with a
--     'Vulkan.Core10.Handles.PipelineLayout' that is compatible for set
--     /n/, with the 'Vulkan.Core10.Handles.PipelineLayout' used to create
--     the current 'Vulkan.Core10.Handles.Pipeline', as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???>
--
-- -   For each push constant that is statically used by the
--     'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point
--     used by this command, a push constant value /must/ have been set for
--     the same pipeline bind point, with a
--     'Vulkan.Core10.Handles.PipelineLayout' that is compatible for push
--     constants, with the 'Vulkan.Core10.Handles.PipelineLayout' used to
--     create the current 'Vulkan.Core10.Handles.Pipeline', as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???>
--
-- -   Descriptors in each bound descriptor set, specified via
--     'Vulkan.Core10.CommandBufferBuilding.cmdBindDescriptorSets', /must/
--     be valid if they are statically used by the
--     'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point
--     used by this command
--
-- -   A valid pipeline /must/ be bound to the pipeline bind point used by
--     this command
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command requires any dynamic state, that
--     state /must/ have been set for @commandBuffer@, and done so after
--     any previously bound pipeline with the corresponding state not
--     specified as dynamic
--
-- -   There /must/ not have been any calls to dynamic state setting
--     commands for any state not specified as dynamic in the
--     'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind
--     point used by this command, since that pipeline was bound
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command accesses a
--     'Vulkan.Core10.Handles.Sampler' object that uses unnormalized
--     coordinates, that sampler /must/ not be used to sample from any
--     'Vulkan.Core10.Handles.Image' with a
--     'Vulkan.Core10.Handles.ImageView' of the type
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D',
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE',
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY',
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in
--     any shader stage
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command accesses a
--     'Vulkan.Core10.Handles.Sampler' object that uses unnormalized
--     coordinates, that sampler /must/ not be used with any of the SPIR-V
--     @OpImageSample*@ or @OpImageSparseSample*@ instructions with
--     @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command accesses a
--     'Vulkan.Core10.Handles.Sampler' object that uses unnormalized
--     coordinates, that sampler /must/ not be used with any of the SPIR-V
--     @OpImageSample*@ or @OpImageSparseSample*@ instructions that
--     includes a LOD bias or any offset values, in any shader stage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access>
--     feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline'
--     object bound to the pipeline bind point used by this command
--     accesses a uniform buffer, it /must/ not access values outside of
--     the range of the buffer as specified in the descriptor set bound to
--     the same pipeline bind point
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access>
--     feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline'
--     object bound to the pipeline bind point used by this command
--     accesses a storage buffer, it /must/ not access values outside of
--     the range of the buffer as specified in the descriptor set bound to
--     the same pipeline bind point
--
-- -   If @commandBuffer@ is an unprotected command buffer, any resource
--     accessed by the 'Vulkan.Core10.Handles.Pipeline' object bound to the
--     pipeline bind point used by this command /must/ not be a protected
--     resource
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is accessed using
--     @OpImageWrite@ as a result of this command, then the @Type@ of the
--     @Texel@ operand of that instruction /must/ have at least as many
--     components as the image view’s format.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' is accessed using
--     @OpImageWrite@ as a result of this command, then the @Type@ of the
--     @Texel@ operand of that instruction /must/ have at least as many
--     components as the image view’s format.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Image' objects
--     created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects
--     created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   Any shader group handle referenced by this call /must/ have been
--     queried from the currently bound ray tracing shader pipeline
--
-- -   This command /must/ not cause a shader call instruction to be
--     executed from a shader invocation with a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#ray-tracing-recursion-depth recursion depth>
--     greater than the value of @maxRecursionDepth@ used to create the
--     bound ray tracing pipeline
--
-- -   If @pRayGenShaderBindingTable->buffer@ is non-sparse then it /must/
--     be bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   The @offset@ member of @pRayGenShaderBindingTable@ /must/ be less
--     than the size of the @pRayGenShaderBindingTable->buffer@
--
-- -   @pRayGenShaderBindingTable->offset@ /must/ be a multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupBaseAlignment@
--
-- -   @pRayGenShaderBindingTable->offset@ +
--     @pRayGenShaderBindingTable->size@ /must/ be less than or equal to
--     the size of @pRayGenShaderBindingTable->buffer@
--
-- -   The @size@ member of @pRayGenShaderBindingTable@ /must/ be equal to
--     its @stride@ member
--
-- -   If @pMissShaderBindingTable->buffer@ is non-sparse then it /must/ be
--     bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   The @offset@ member of @pMissShaderBindingTable@ /must/ be less than
--     the size of @pMissShaderBindingTable->buffer@
--
-- -   The @offset@ member of @pMissShaderBindingTable@ /must/ be a
--     multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupBaseAlignment@
--
-- -   @pMissShaderBindingTable->offset@ + @pMissShaderBindingTable->size@
--     /must/ be less than or equal to the size of
--     @pMissShaderBindingTable->buffer@
--
-- -   The @stride@ member of @pMissShaderBindingTable@ /must/ be a
--     multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupHandleSize@
--
-- -   The @stride@ member of @pMissShaderBindingTable@ /must/ be less than
--     or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxShaderGroupStride@
--
-- -   If @pHitShaderBindingTable->buffer@ is non-sparse then it /must/ be
--     bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   The @offset@ member of @pHitShaderBindingTable@ /must/ be less than
--     the size of @pHitShaderBindingTable->buffer@
--
-- -   The @offset@ member of @pHitShaderBindingTable@ /must/ be a multiple
--     of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupBaseAlignment@
--
-- -   @pHitShaderBindingTable->offset@ + @pHitShaderBindingTable->size@
--     /must/ be less than or equal to the size of
--     @pHitShaderBindingTable->buffer@
--
-- -   The @stride@ member of @pHitShaderBindingTable@ /must/ be a multiple
--     of 'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupHandleSize@
--
-- -   The @stride@ member of @pHitShaderBindingTable@ /must/ be less than
--     or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxShaderGroupStride@
--
-- -   If @pCallableShaderBindingTable->buffer@ is non-sparse then it
--     /must/ be bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   The @offset@ member of @pCallableShaderBindingTable@ /must/ be less
--     than the size of @pCallableShaderBindingTable->buffer@
--
-- -   The @offset@ member of @pCallableShaderBindingTable@ /must/ be a
--     multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupBaseAlignment@
--
-- -   @pCallableShaderBindingTable->offset@ +
--     @pCallableShaderBindingTable->size@ /must/ be less than or equal to
--     the size of @pCallableShaderBindingTable->buffer@
--
-- -   The @stride@ member of @pCallableShaderBindingTable@ /must/ be a
--     multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupHandleSize@
--
-- -   The @stride@ member of @pCallableShaderBindingTable@ /must/ be less
--     than or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxShaderGroupStride@
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR',
--     the @buffer@ member of @pHitShaderBindingTable@ /must/ not be
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR',
--     the @buffer@ member of @pHitShaderBindingTable@ /must/ not be
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR',
--     the @buffer@ member of @pHitShaderBindingTable@ /must/ not be
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR',
--     the shader group handle identified by @pMissShaderBindingTable@
--     /must/ contain a valid miss shader
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR',
--     entries in @pHitShaderBindingTable@ accessed as a result of this
--     command in order to execute an any hit shader /must/ not be set to
--     zero
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR',
--     entries in @pHitShaderBindingTable@ accessed as a result of this
--     command in order to execute a closest hit shader /must/ not be set
--     to zero
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR',
--     entries in @pHitShaderBindingTable@ accessed as a result of this
--     command in order to execute an intersection shader /must/ not be set
--     to zero
--
-- -   If @commandBuffer@ is a protected command buffer, any resource
--     written to by the 'Vulkan.Core10.Handles.Pipeline' object bound to
--     the pipeline bind point used by this command /must/ not be an
--     unprotected resource
--
-- -   If @commandBuffer@ is a protected command buffer, pipeline stages
--     other than the framebuffer-space and compute stages in the
--     'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind
--     point /must/ not write to any resource
--
-- -   @width@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0]
--
-- -   @height@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1]
--
-- -   @depth@ /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2]
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pRaygenShaderBindingTable@ /must/ be a valid pointer to a valid
--     'StridedBufferRegionKHR' structure
--
-- -   @pMissShaderBindingTable@ /must/ be a valid pointer to a valid
--     'StridedBufferRegionKHR' structure
--
-- -   @pHitShaderBindingTable@ /must/ be a valid pointer to a valid
--     'StridedBufferRegionKHR' structure
--
-- -   @pCallableShaderBindingTable@ /must/ be a valid pointer to a valid
--     'StridedBufferRegionKHR' structure
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- == 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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Compute                                                                                                               |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer', 'StridedBufferRegionKHR'
cmdTraceRaysKHR :: forall io
                 . (MonadIO io)
                => -- | @commandBuffer@ is the command buffer into which the command will be
                   -- recorded.
                   CommandBuffer
                -> -- | @pRaygenShaderBindingTable@ is a 'StridedBufferRegionKHR' that holds the
                   -- shader binding table data for the ray generation shader stage.
                   ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
                -> -- | @pMissShaderBindingTable@ is a 'StridedBufferRegionKHR' that holds the
                   -- shader binding table data for the miss shader stage.
                   ("missShaderBindingTable" ::: StridedBufferRegionKHR)
                -> -- | @pHitShaderBindingTable@ is a 'StridedBufferRegionKHR' that holds the
                   -- shader binding table data for the hit shader stage.
                   ("hitShaderBindingTable" ::: StridedBufferRegionKHR)
                -> -- | @pCallableShaderBindingTable@ is a 'StridedBufferRegionKHR' that holds
                   -- the shader binding table data for the callable shader stage.
                   ("callableShaderBindingTable" ::: StridedBufferRegionKHR)
                -> -- | @width@ is the width of the ray trace query dimensions.
                   ("width" ::: Word32)
                -> -- | @height@ is height of the ray trace query dimensions.
                   ("height" ::: Word32)
                -> -- | @depth@ is depth of the ray trace query dimensions.
                   ("depth" ::: Word32)
                -> io ()
cmdTraceRaysKHR :: CommandBuffer
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> io ()
cmdTraceRaysKHR commandBuffer :: CommandBuffer
commandBuffer raygenShaderBindingTable :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
raygenShaderBindingTable missShaderBindingTable :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
missShaderBindingTable hitShaderBindingTable :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
hitShaderBindingTable callableShaderBindingTable :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
callableShaderBindingTable width :: "bindInfoCount" ::: Word32
width height :: "bindInfoCount" ::: Word32
height depth :: "bindInfoCount" ::: Word32
depth = 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 vkCmdTraceRaysKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
vkCmdTraceRaysKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("bindInfoCount" ::: Word32)
      -> ("bindInfoCount" ::: Word32)
      -> ("bindInfoCount" ::: Word32)
      -> IO ())
pVkCmdTraceRaysKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
vkCmdTraceRaysKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("bindInfoCount" ::: Word32)
      -> ("bindInfoCount" ::: Word32)
      -> ("bindInfoCount" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> 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 "" "The function pointer for vkCmdTraceRaysKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdTraceRaysKHR' :: Ptr CommandBuffer_T
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> IO ()
vkCmdTraceRaysKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> IO ()
mkVkCmdTraceRaysKHR FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
vkCmdTraceRaysKHRPtr
  "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pRaygenShaderBindingTable <- ((("pRaygenShaderBindingTable"
   ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)))
-> ((("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall a b. (a -> b) -> a -> b
$ ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("raygenShaderBindingTable" ::: StridedBufferRegionKHR
raygenShaderBindingTable)
  "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pMissShaderBindingTable <- ((("pRaygenShaderBindingTable"
   ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)))
-> ((("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall a b. (a -> b) -> a -> b
$ ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("raygenShaderBindingTable" ::: StridedBufferRegionKHR
missShaderBindingTable)
  "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pHitShaderBindingTable <- ((("pRaygenShaderBindingTable"
   ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)))
-> ((("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall a b. (a -> b) -> a -> b
$ ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("raygenShaderBindingTable" ::: StridedBufferRegionKHR
hitShaderBindingTable)
  "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pCallableShaderBindingTable <- ((("pRaygenShaderBindingTable"
   ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)))
-> ((("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall a b. (a -> b) -> a -> b
$ ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("raygenShaderBindingTable" ::: StridedBufferRegionKHR
callableShaderBindingTable)
  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
$ Ptr CommandBuffer_T
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> IO ()
vkCmdTraceRaysKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pRaygenShaderBindingTable "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pMissShaderBindingTable "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pHitShaderBindingTable "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pCallableShaderBindingTable ("bindInfoCount" ::: Word32
width) ("bindInfoCount" ::: Word32
height) ("bindInfoCount" ::: Word32
depth)
  () -> 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" mkVkGetRayTracingShaderGroupHandlesKHR
  :: FunPtr (Ptr Device_T -> Pipeline -> Word32 -> Word32 -> CSize -> Ptr () -> IO Result) -> Ptr Device_T -> Pipeline -> Word32 -> Word32 -> CSize -> Ptr () -> IO Result

-- | vkGetRayTracingShaderGroupHandlesKHR - Query ray tracing pipeline shader
-- group handles
--
-- == Valid Usage
--
-- -   @firstGroup@ /must/ be less than the number of shader groups in
--     @pipeline@
--
-- -   The sum of @firstGroup@ and @groupCount@ /must/ be less than or
--     equal to the number of shader groups in @pipeline@
--
-- -   @dataSize@ /must/ be at least
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupHandleSize@ ×
--     @groupCount@
--
-- -   @pipeline@ /must/ have not been created with
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_LIBRARY_BIT_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pipeline@ /must/ be a valid 'Vulkan.Core10.Handles.Pipeline' handle
--
-- -   @pData@ /must/ be a valid pointer to an array of @dataSize@ bytes
--
-- -   @dataSize@ /must/ be greater than @0@
--
-- -   @pipeline@ /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
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Pipeline'
getRayTracingShaderGroupHandlesKHR :: forall io
                                    . (MonadIO io)
                                   => -- | @device@ is the logical device containing the ray tracing pipeline.
                                      Device
                                   -> -- | @pipeline@ is the ray tracing pipeline object containing the shaders.
                                      Pipeline
                                   -> -- | @firstGroup@ is the index of the first group to retrieve a handle for
                                      -- from the 'RayTracingPipelineCreateInfoKHR'::@pGroups@ or
                                      -- 'Vulkan.Extensions.VK_NV_ray_tracing.RayTracingPipelineCreateInfoNV'::@pGroups@
                                      -- array.
                                      ("firstGroup" ::: Word32)
                                   -> -- | @groupCount@ is the number of shader handles to retrieve.
                                      ("groupCount" ::: Word32)
                                   -> -- | @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 ())
                                   -> io ()
getRayTracingShaderGroupHandlesKHR :: Device
-> Pipeline
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: Word64)
-> ("data" ::: Ptr ())
-> io ()
getRayTracingShaderGroupHandlesKHR device :: Device
device pipeline :: Pipeline
pipeline firstGroup :: "bindInfoCount" ::: Word32
firstGroup groupCount :: "bindInfoCount" ::: Word32
groupCount dataSize :: "dataSize" ::: Word64
dataSize data' :: "data" ::: Ptr ()
data' = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkGetRayTracingShaderGroupHandlesKHRPtr :: FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
vkGetRayTracingShaderGroupHandlesKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Pipeline
      -> ("bindInfoCount" ::: Word32)
      -> ("bindInfoCount" ::: Word32)
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> IO Result)
pVkGetRayTracingShaderGroupHandlesKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
vkGetRayTracingShaderGroupHandlesKHRPtr FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> Pipeline
      -> ("bindInfoCount" ::: Word32)
      -> ("bindInfoCount" ::: Word32)
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> 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 "" "The function pointer for vkGetRayTracingShaderGroupHandlesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetRayTracingShaderGroupHandlesKHR' :: Ptr Device_T
-> Pipeline
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> IO Result
vkGetRayTracingShaderGroupHandlesKHR' = FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
-> Ptr Device_T
-> Pipeline
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> IO Result
mkVkGetRayTracingShaderGroupHandlesKHR FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
vkGetRayTracingShaderGroupHandlesKHRPtr
  Result
r <- Ptr Device_T
-> Pipeline
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> IO Result
vkGetRayTracingShaderGroupHandlesKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Pipeline
pipeline) ("bindInfoCount" ::: Word32
firstGroup) ("bindInfoCount" ::: Word32
groupCount) (("dataSize" ::: Word64) -> "dataSize" ::: CSize
CSize ("dataSize" ::: Word64
dataSize)) ("data" ::: Ptr ()
data')
  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" mkVkGetRayTracingCaptureReplayShaderGroupHandlesKHR
  :: FunPtr (Ptr Device_T -> Pipeline -> Word32 -> Word32 -> CSize -> Ptr () -> IO Result) -> Ptr Device_T -> Pipeline -> Word32 -> Word32 -> CSize -> Ptr () -> IO Result

-- | vkGetRayTracingCaptureReplayShaderGroupHandlesKHR - Query ray tracing
-- capture replay pipeline shader group handles
--
-- == Valid Usage
--
-- -   @firstGroup@ /must/ be less than the number of shader groups in
--     @pipeline@
--
-- -   The sum of @firstGroup@ and @groupCount@ /must/ be less than or
--     equal to the number of shader groups in @pipeline@
--
-- -   @dataSize@ /must/ be at least
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupHandleCaptureReplaySize@
--     × @groupCount@
--
-- -   'PhysicalDeviceRayTracingFeaturesKHR'::@rayTracingShaderGroupHandleCaptureReplay@
--     /must/ be enabled to call this function
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pipeline@ /must/ be a valid 'Vulkan.Core10.Handles.Pipeline' handle
--
-- -   @pData@ /must/ be a valid pointer to an array of @dataSize@ bytes
--
-- -   @dataSize@ /must/ be greater than @0@
--
-- -   @pipeline@ /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
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Pipeline'
getRayTracingCaptureReplayShaderGroupHandlesKHR :: forall io
                                                 . (MonadIO io)
                                                => -- | @device@ is the logical device containing the ray tracing pipeline.
                                                   Device
                                                -> -- | @pipeline@ is the ray tracing pipeline object containing the shaders.
                                                   Pipeline
                                                -> -- | @firstGroup@ is the index of the first group to retrieve a handle for
                                                   -- from the 'RayTracingPipelineCreateInfoKHR'::@pGroups@ array.
                                                   ("firstGroup" ::: Word32)
                                                -> -- | @groupCount@ is the number of shader handles to retrieve.
                                                   ("groupCount" ::: Word32)
                                                -> -- | @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 ())
                                                -> io ()
getRayTracingCaptureReplayShaderGroupHandlesKHR :: Device
-> Pipeline
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: Word64)
-> ("data" ::: Ptr ())
-> io ()
getRayTracingCaptureReplayShaderGroupHandlesKHR device :: Device
device pipeline :: Pipeline
pipeline firstGroup :: "bindInfoCount" ::: Word32
firstGroup groupCount :: "bindInfoCount" ::: Word32
groupCount dataSize :: "dataSize" ::: Word64
dataSize data' :: "data" ::: Ptr ()
data' = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkGetRayTracingCaptureReplayShaderGroupHandlesKHRPtr :: FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
vkGetRayTracingCaptureReplayShaderGroupHandlesKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Pipeline
      -> ("bindInfoCount" ::: Word32)
      -> ("bindInfoCount" ::: Word32)
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> IO Result)
pVkGetRayTracingCaptureReplayShaderGroupHandlesKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
vkGetRayTracingCaptureReplayShaderGroupHandlesKHRPtr FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> Pipeline
      -> ("bindInfoCount" ::: Word32)
      -> ("bindInfoCount" ::: Word32)
      -> ("dataSize" ::: CSize)
      -> ("data" ::: Ptr ())
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> 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 "" "The function pointer for vkGetRayTracingCaptureReplayShaderGroupHandlesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetRayTracingCaptureReplayShaderGroupHandlesKHR' :: Ptr Device_T
-> Pipeline
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> IO Result
vkGetRayTracingCaptureReplayShaderGroupHandlesKHR' = FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
-> Ptr Device_T
-> Pipeline
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> IO Result
mkVkGetRayTracingCaptureReplayShaderGroupHandlesKHR FunPtr
  (Ptr Device_T
   -> Pipeline
   -> ("bindInfoCount" ::: Word32)
   -> ("bindInfoCount" ::: Word32)
   -> ("dataSize" ::: CSize)
   -> ("data" ::: Ptr ())
   -> IO Result)
vkGetRayTracingCaptureReplayShaderGroupHandlesKHRPtr
  Result
r <- Ptr Device_T
-> Pipeline
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: CSize)
-> ("data" ::: Ptr ())
-> IO Result
vkGetRayTracingCaptureReplayShaderGroupHandlesKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Pipeline
pipeline) ("bindInfoCount" ::: Word32
firstGroup) ("bindInfoCount" ::: Word32
groupCount) (("dataSize" ::: Word64) -> "dataSize" ::: CSize
CSize ("dataSize" ::: Word64
dataSize)) ("data" ::: Ptr ()
data')
  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" mkVkCreateRayTracingPipelinesKHR
  :: FunPtr (Ptr Device_T -> PipelineCache -> Word32 -> Ptr (SomeStruct RayTracingPipelineCreateInfoKHR) -> Ptr AllocationCallbacks -> Ptr Pipeline -> IO Result) -> Ptr Device_T -> PipelineCache -> Word32 -> Ptr (SomeStruct RayTracingPipelineCreateInfoKHR) -> Ptr AllocationCallbacks -> Ptr Pipeline -> IO Result

-- | vkCreateRayTracingPipelinesKHR - Creates a new ray tracing pipeline
-- object
--
-- = Description
--
-- The 'Vulkan.Core10.Enums.Result.ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS'
-- error is returned if the implementation is unable to re-use the shader
-- group handles provided in
-- 'RayTracingShaderGroupCreateInfoKHR'::@pShaderGroupCaptureReplayHandle@
-- when
-- 'PhysicalDeviceRayTracingFeaturesKHR'::@rayTracingShaderGroupHandleCaptureReplay@
-- is enabled.
--
-- == Valid Usage
--
-- -   If the @flags@ member of any element of @pCreateInfos@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and the @basePipelineIndex@ member of that same element is not
--     @-1@, @basePipelineIndex@ /must/ be less than the index into
--     @pCreateInfos@ that corresponds to that element
--
-- -   If the @flags@ member of any element of @pCreateInfos@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, the base pipeline /must/ have been created with the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_ALLOW_DERIVATIVES_BIT'
--     flag set
--
-- -   If @pipelineCache@ was created with
--     'Vulkan.Core10.Enums.PipelineCacheCreateFlagBits.PIPELINE_CACHE_CREATE_EXTERNALLY_SYNCHRONIZED_BIT_EXT',
--     host access to @pipelineCache@ /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-threadingbehavior externally synchronized>
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing rayTracing>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @pipelineCache@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @pipelineCache@ /must/ be a valid
--     'Vulkan.Core10.Handles.PipelineCache' handle
--
-- -   @pCreateInfos@ /must/ be a valid pointer to an array of
--     @createInfoCount@ valid 'RayTracingPipelineCreateInfoKHR' structures
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pPipelines@ /must/ be a valid pointer to an array of
--     @createInfoCount@ 'Vulkan.Core10.Handles.Pipeline' handles
--
-- -   @createInfoCount@ /must/ be greater than @0@
--
-- -   If @pipelineCache@ 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'
--
--     -   'Vulkan.Core10.Enums.Result.PIPELINE_COMPILE_REQUIRED_EXT'
--
-- [<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'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_INVALID_OPAQUE_CAPTURE_ADDRESS'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Pipeline',
-- 'Vulkan.Core10.Handles.PipelineCache', 'RayTracingPipelineCreateInfoKHR'
createRayTracingPipelinesKHR :: forall io
                              . (MonadIO io)
                             => -- | @device@ is the logical device that creates the ray tracing pipelines.
                                Device
                             -> -- | @pipelineCache@ is either 'Vulkan.Core10.APIConstants.NULL_HANDLE',
                                -- indicating that pipeline caching is disabled, or the handle of a valid
                                -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipelines-cache pipeline cache>
                                -- object, in which case use of that cache is enabled for the duration of
                                -- the command.
                                PipelineCache
                             -> -- | @pCreateInfos@ is a pointer to an array of
                                -- 'RayTracingPipelineCreateInfoKHR' structures.
                                ("createInfos" ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
                             -> -- | @pAllocator@ controls host memory allocation as described in the
                                -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                                -- chapter.
                                ("allocator" ::: Maybe AllocationCallbacks)
                             -> io (Result, ("pipelines" ::: Vector Pipeline))
createRayTracingPipelinesKHR :: Device
-> PipelineCache
-> ("createInfos"
    ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io (Result, "pipelines" ::: Vector Pipeline)
createRayTracingPipelinesKHR device :: Device
device pipelineCache :: PipelineCache
pipelineCache createInfos :: "createInfos"
::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR)
createInfos allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO (Result, "pipelines" ::: Vector Pipeline)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "pipelines" ::: Vector Pipeline)
 -> io (Result, "pipelines" ::: Vector Pipeline))
-> (ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      (Result, "pipelines" ::: Vector Pipeline)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "pipelines" ::: Vector Pipeline)
  IO
  (Result, "pipelines" ::: Vector Pipeline)
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "pipelines" ::: Vector Pipeline)
   IO
   (Result, "pipelines" ::: Vector Pipeline)
 -> io (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
-> io (Result, "pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateRayTracingPipelinesKHRPtr :: FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("bindInfoCount" ::: Word32)
   -> ("pCreateInfos"
       ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
vkCreateRayTracingPipelinesKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("bindInfoCount" ::: Word32)
      -> ("pCreateInfos"
          ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pPipelines" ::: Ptr Pipeline)
      -> IO Result)
pVkCreateRayTracingPipelinesKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("bindInfoCount" ::: Word32)
   -> ("pCreateInfos"
       ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
vkCreateRayTracingPipelinesKHRPtr FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("bindInfoCount" ::: Word32)
   -> ("pCreateInfos"
       ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("bindInfoCount" ::: Word32)
      -> ("pCreateInfos"
          ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pPipelines" ::: Ptr Pipeline)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("bindInfoCount" ::: Word32)
   -> ("pCreateInfos"
       ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> 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 "" "The function pointer for vkCreateRayTracingPipelinesKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateRayTracingPipelinesKHR' :: Ptr Device_T
-> PipelineCache
-> ("bindInfoCount" ::: Word32)
-> ("pCreateInfos"
    ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelines" ::: Ptr Pipeline)
-> IO Result
vkCreateRayTracingPipelinesKHR' = FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("bindInfoCount" ::: Word32)
   -> ("pCreateInfos"
       ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
-> Ptr Device_T
-> PipelineCache
-> ("bindInfoCount" ::: Word32)
-> ("pCreateInfos"
    ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelines" ::: Ptr Pipeline)
-> IO Result
mkVkCreateRayTracingPipelinesKHR FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("bindInfoCount" ::: Word32)
   -> ("pCreateInfos"
       ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelines" ::: Ptr Pipeline)
   -> IO Result)
vkCreateRayTracingPipelinesKHRPtr
  Ptr (RayTracingPipelineCreateInfoKHR Any)
pPCreateInfos <- ((Ptr (RayTracingPipelineCreateInfoKHR Any)
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Ptr (RayTracingPipelineCreateInfoKHR Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (RayTracingPipelineCreateInfoKHR Any)
   -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      (Ptr (RayTracingPipelineCreateInfoKHR Any)))
-> ((Ptr (RayTracingPipelineCreateInfoKHR Any)
     -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Ptr (RayTracingPipelineCreateInfoKHR Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr (RayTracingPipelineCreateInfoKHR Any)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(RayTracingPipelineCreateInfoKHR _) ((("createInfos"
 ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("createInfos"
::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR)
createInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 120) 8
  (Int
 -> SomeStruct RayTracingPipelineCreateInfoKHR
 -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> ("createInfos"
    ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct RayTracingPipelineCreateInfoKHR
e -> ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall a b. (a -> b) -> a -> b
$ ("pCreateInfos"
 ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
-> SomeStruct RayTracingPipelineCreateInfoKHR
-> IO (Result, "pipelines" ::: Vector Pipeline)
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (RayTracingPipelineCreateInfoKHR Any)
-> "pCreateInfos"
   ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (RayTracingPipelineCreateInfoKHR Any)
pPCreateInfos Ptr (RayTracingPipelineCreateInfoKHR Any)
-> Int -> Ptr (RayTracingPipelineCreateInfoKHR _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (120 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (RayTracingPipelineCreateInfoKHR _))) (SomeStruct RayTracingPipelineCreateInfoKHR
e) (IO (Result, "pipelines" ::: Vector Pipeline)
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> (() -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO (Result, "pipelines" ::: Vector Pipeline))
-> () -> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ ())) ("createInfos"
::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR)
createInfos)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks)
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     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 (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks)
     -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pPipelines" ::: Ptr Pipeline
pPPipelines <- ((("pPipelines" ::: Ptr Pipeline)
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pPipelines" ::: Ptr Pipeline)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPipelines" ::: Ptr Pipeline)
   -> IO (Result, "pipelines" ::: Vector Pipeline))
  -> IO (Result, "pipelines" ::: Vector Pipeline))
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      ("pPipelines" ::: Ptr Pipeline))
-> ((("pPipelines" ::: Ptr Pipeline)
     -> IO (Result, "pipelines" ::: Vector Pipeline))
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pPipelines" ::: Ptr Pipeline)
forall a b. (a -> b) -> a -> b
$ IO ("pPipelines" ::: Ptr Pipeline)
-> (("pPipelines" ::: Ptr Pipeline) -> IO ())
-> (("pPipelines" ::: Ptr Pipeline)
    -> IO (Result, "pipelines" ::: Vector Pipeline))
-> IO (Result, "pipelines" ::: Vector Pipeline)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPipelines" ::: Ptr Pipeline)
forall a. Int -> IO (Ptr a)
callocBytes @Pipeline ((("bindInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("createInfos"
 ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfos"
  ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
 -> Int)
-> ("createInfos"
    ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
-> Int
forall a b. (a -> b) -> a -> b
$ ("createInfos"
::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR)
createInfos)) :: Word32))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8)) ("pPipelines" ::: Ptr Pipeline) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
 -> ContT (Result, "pipelines" ::: Vector Pipeline) IO Result)
-> IO Result
-> ContT (Result, "pipelines" ::: Vector Pipeline) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> PipelineCache
-> ("bindInfoCount" ::: Word32)
-> ("pCreateInfos"
    ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelines" ::: Ptr Pipeline)
-> IO Result
vkCreateRayTracingPipelinesKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (PipelineCache
pipelineCache) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("createInfos"
 ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfos"
  ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
 -> Int)
-> ("createInfos"
    ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
-> Int
forall a b. (a -> b) -> a -> b
$ ("createInfos"
::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR)
createInfos)) :: Word32)) (Ptr (RayTracingPipelineCreateInfoKHR Any)
-> "pCreateInfos"
   ::: Ptr (SomeStruct RayTracingPipelineCreateInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (RayTracingPipelineCreateInfoKHR Any)
pPCreateInfos)) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pPipelines" ::: Ptr Pipeline
pPPipelines)
  IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) IO ())
-> IO () -> ContT (Result, "pipelines" ::: Vector Pipeline) 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))
  "pipelines" ::: Vector Pipeline
pPipelines <- IO ("pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pipelines" ::: Vector Pipeline)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("pipelines" ::: Vector Pipeline)
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      ("pipelines" ::: Vector Pipeline))
-> IO ("pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     ("pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ Int -> (Int -> IO Pipeline) -> IO ("pipelines" ::: Vector Pipeline)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("bindInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("createInfos"
 ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfos"
  ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
 -> Int)
-> ("createInfos"
    ::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR))
-> Int
forall a b. (a -> b) -> a -> b
$ ("createInfos"
::: Vector (SomeStruct RayTracingPipelineCreateInfoKHR)
createInfos)) :: Word32))) (\i :: Int
i -> ("pPipelines" ::: Ptr Pipeline) -> IO Pipeline
forall a. Storable a => Ptr a -> IO a
peek @Pipeline (("pPipelines" ::: Ptr Pipeline
pPPipelines ("pPipelines" ::: Ptr Pipeline)
-> Int -> "pPipelines" ::: Ptr Pipeline
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Pipeline)))
  (Result, "pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "pipelines" ::: Vector Pipeline)
 -> ContT
      (Result, "pipelines" ::: Vector Pipeline)
      IO
      (Result, "pipelines" ::: Vector Pipeline))
-> (Result, "pipelines" ::: Vector Pipeline)
-> ContT
     (Result, "pipelines" ::: Vector Pipeline)
     IO
     (Result, "pipelines" ::: Vector Pipeline)
forall a b. (a -> b) -> a -> b
$ (Result
r, "pipelines" ::: Vector Pipeline
pPipelines)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdTraceRaysIndirectKHR
  :: FunPtr (Ptr CommandBuffer_T -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Buffer -> DeviceSize -> IO ()) -> Ptr CommandBuffer_T -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Ptr StridedBufferRegionKHR -> Buffer -> DeviceSize -> IO ()

-- | vkCmdTraceRaysIndirectKHR - Initialize an indirect ray tracing dispatch
--
-- = Description
--
-- 'cmdTraceRaysIndirectKHR' behaves similarly to 'cmdTraceRaysKHR' except
-- that the ray trace query dimensions are read by the device from @buffer@
-- during execution. The parameters of trace ray are encoded in the
-- 'TraceRaysIndirectCommandKHR' structure located at @offset@ bytes in
-- @buffer@.
--
-- == Valid Usage
--
-- -   If a 'Vulkan.Core10.Handles.Sampler' created with @magFilter@ or
--     @minFilter@ equal to 'Vulkan.Core10.Enums.Filter.FILTER_LINEAR' and
--     @compareEnable@ equal to 'Vulkan.Core10.FundamentalTypes.FALSE' is
--     used to sample a 'Vulkan.Core10.Handles.ImageView' as a result of
--     this command, then the image view’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features>
--     /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_LINEAR_BIT'
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is accessed using atomic
--     operations as a result of this command, then the image view’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features>
--     /must/ contain
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_STORAGE_IMAGE_ATOMIC_BIT'
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is sampled with
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result
--     of this command, then the image view’s
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-image-view-format-features format features>
--     /must/ contain
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FORMAT_FEATURE_SAMPLED_IMAGE_FILTER_CUBIC_BIT_EXT'
--
-- -   Any 'Vulkan.Core10.Handles.ImageView' being sampled with
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' as a result
--     of this command /must/ have a
--     'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that
--     supports cubic filtering, as specified by
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubic@
--     returned by
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2'
--
-- -   Any 'Vulkan.Core10.Handles.ImageView' being sampled with
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FILTER_CUBIC_EXT' with a
--     reduction mode of either
--     'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MIN'
--     or
--     'Vulkan.Core12.Enums.SamplerReductionMode.SAMPLER_REDUCTION_MODE_MAX'
--     as a result of this command /must/ have a
--     'Vulkan.Core10.Enums.ImageViewType.ImageViewType' and format that
--     supports cubic filtering together with minmax filtering, as
--     specified by
--     'Vulkan.Extensions.VK_EXT_filter_cubic.FilterCubicImageViewImageFormatPropertiesEXT'::@filterCubicMinmax@
--     returned by
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceImageFormatProperties2'
--
-- -   Any 'Vulkan.Core10.Handles.Image' created with a
--     'Vulkan.Core10.Image.ImageCreateInfo'::@flags@ containing
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_CORNER_SAMPLED_BIT_NV'
--     sampled as a result of this command /must/ only be sampled using a
--     'Vulkan.Core10.Enums.SamplerAddressMode.SamplerAddressMode' of
--     'Vulkan.Core10.Enums.SamplerAddressMode.SAMPLER_ADDRESS_MODE_CLAMP_TO_EDGE'
--
-- -   For each set /n/ that is statically used by the
--     'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point
--     used by this command, a descriptor set /must/ have been bound to /n/
--     at the same pipeline bind point, with a
--     'Vulkan.Core10.Handles.PipelineLayout' that is compatible for set
--     /n/, with the 'Vulkan.Core10.Handles.PipelineLayout' used to create
--     the current 'Vulkan.Core10.Handles.Pipeline', as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???>
--
-- -   For each push constant that is statically used by the
--     'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point
--     used by this command, a push constant value /must/ have been set for
--     the same pipeline bind point, with a
--     'Vulkan.Core10.Handles.PipelineLayout' that is compatible for push
--     constants, with the 'Vulkan.Core10.Handles.PipelineLayout' used to
--     create the current 'Vulkan.Core10.Handles.Pipeline', as described in
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility ???>
--
-- -   Descriptors in each bound descriptor set, specified via
--     'Vulkan.Core10.CommandBufferBuilding.cmdBindDescriptorSets', /must/
--     be valid if they are statically used by the
--     'Vulkan.Core10.Handles.Pipeline' bound to the pipeline bind point
--     used by this command
--
-- -   A valid pipeline /must/ be bound to the pipeline bind point used by
--     this command
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command requires any dynamic state, that
--     state /must/ have been set for @commandBuffer@, and done so after
--     any previously bound pipeline with the corresponding state not
--     specified as dynamic
--
-- -   There /must/ not have been any calls to dynamic state setting
--     commands for any state not specified as dynamic in the
--     'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline bind
--     point used by this command, since that pipeline was bound
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command accesses a
--     'Vulkan.Core10.Handles.Sampler' object that uses unnormalized
--     coordinates, that sampler /must/ not be used to sample from any
--     'Vulkan.Core10.Handles.Image' with a
--     'Vulkan.Core10.Handles.ImageView' of the type
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_3D',
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE',
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_1D_ARRAY',
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_2D_ARRAY' or
--     'Vulkan.Core10.Enums.ImageViewType.IMAGE_VIEW_TYPE_CUBE_ARRAY', in
--     any shader stage
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command accesses a
--     'Vulkan.Core10.Handles.Sampler' object that uses unnormalized
--     coordinates, that sampler /must/ not be used with any of the SPIR-V
--     @OpImageSample*@ or @OpImageSparseSample*@ instructions with
--     @ImplicitLod@, @Dref@ or @Proj@ in their name, in any shader stage
--
-- -   If the 'Vulkan.Core10.Handles.Pipeline' object bound to the pipeline
--     bind point used by this command accesses a
--     'Vulkan.Core10.Handles.Sampler' object that uses unnormalized
--     coordinates, that sampler /must/ not be used with any of the SPIR-V
--     @OpImageSample*@ or @OpImageSparseSample*@ instructions that
--     includes a LOD bias or any offset values, in any shader stage
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access>
--     feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline'
--     object bound to the pipeline bind point used by this command
--     accesses a uniform buffer, it /must/ not access values outside of
--     the range of the buffer as specified in the descriptor set bound to
--     the same pipeline bind point
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-robustBufferAccess robust buffer access>
--     feature is not enabled, and if the 'Vulkan.Core10.Handles.Pipeline'
--     object bound to the pipeline bind point used by this command
--     accesses a storage buffer, it /must/ not access values outside of
--     the range of the buffer as specified in the descriptor set bound to
--     the same pipeline bind point
--
-- -   If @commandBuffer@ is an unprotected command buffer, any resource
--     accessed by the 'Vulkan.Core10.Handles.Pipeline' object bound to the
--     pipeline bind point used by this command /must/ not be a protected
--     resource
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' is accessed using
--     @OpImageWrite@ as a result of this command, then the @Type@ of the
--     @Texel@ operand of that instruction /must/ have at least as many
--     components as the image view’s format.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' is accessed using
--     @OpImageWrite@ as a result of this command, then the @Type@ of the
--     @Texel@ operand of that instruction /must/ have at least as many
--     components as the image view’s format.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.ImageView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a 64-bit channel width
--     is accessed as a result of this command, the @SampledType@ of the
--     @OpTypeImage@ operand of that instruction /must/ have a @Width@ of
--     64.
--
-- -   If a 'Vulkan.Core10.Handles.BufferView' with a
--     'Vulkan.Core10.Enums.Format.Format' that has a channel width less
--     than 64-bit is accessed as a result of this command, the
--     @SampledType@ of the @OpTypeImage@ operand of that instruction
--     /must/ have a @Width@ of 32.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Image' objects
--     created with the
--     'Vulkan.Core10.Enums.ImageCreateFlagBits.IMAGE_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-sparseImageInt64Atomics sparseImageInt64Atomics>
--     feature is not enabled, 'Vulkan.Core10.Handles.Buffer' objects
--     created with the
--     'Vulkan.Core10.Enums.BufferCreateFlagBits.BUFFER_CREATE_SPARSE_RESIDENCY_BIT'
--     flag /must/ not be accessed by atomic instructions through an
--     @OpTypeImage@ with a @SampledType@ with a @Width@ of 64 by this
--     command.
--
-- -   Any shader group handle referenced by this call /must/ have been
--     queried from the currently bound ray tracing shader pipeline
--
-- -   This command /must/ not cause a shader call instruction to be
--     executed from a shader invocation with a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#ray-tracing-recursion-depth recursion depth>
--     greater than the value of @maxRecursionDepth@ used to create the
--     bound ray tracing pipeline
--
-- -   If @pRayGenShaderBindingTable->buffer@ is non-sparse then it /must/
--     be bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   The @offset@ member of @pRayGenShaderBindingTable@ /must/ be less
--     than the size of the @pRayGenShaderBindingTable->buffer@
--
-- -   @pRayGenShaderBindingTable->offset@ /must/ be a multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupBaseAlignment@
--
-- -   @pRayGenShaderBindingTable->offset@ +
--     @pRayGenShaderBindingTable->size@ /must/ be less than or equal to
--     the size of @pRayGenShaderBindingTable->buffer@
--
-- -   The @size@ member of @pRayGenShaderBindingTable@ /must/ be equal to
--     its @stride@ member
--
-- -   If @pMissShaderBindingTable->buffer@ is non-sparse then it /must/ be
--     bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   The @offset@ member of @pMissShaderBindingTable@ /must/ be less than
--     the size of @pMissShaderBindingTable->buffer@
--
-- -   The @offset@ member of @pMissShaderBindingTable@ /must/ be a
--     multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupBaseAlignment@
--
-- -   @pMissShaderBindingTable->offset@ + @pMissShaderBindingTable->size@
--     /must/ be less than or equal to the size of
--     @pMissShaderBindingTable->buffer@
--
-- -   The @stride@ member of @pMissShaderBindingTable@ /must/ be a
--     multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupHandleSize@
--
-- -   The @stride@ member of @pMissShaderBindingTable@ /must/ be less than
--     or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxShaderGroupStride@
--
-- -   If @pHitShaderBindingTable->buffer@ is non-sparse then it /must/ be
--     bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   The @offset@ member of @pHitShaderBindingTable@ /must/ be less than
--     the size of @pHitShaderBindingTable->buffer@
--
-- -   The @offset@ member of @pHitShaderBindingTable@ /must/ be a multiple
--     of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupBaseAlignment@
--
-- -   @pHitShaderBindingTable->offset@ + @pHitShaderBindingTable->size@
--     /must/ be less than or equal to the size of
--     @pHitShaderBindingTable->buffer@
--
-- -   The @stride@ member of @pHitShaderBindingTable@ /must/ be a multiple
--     of 'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupHandleSize@
--
-- -   The @stride@ member of @pHitShaderBindingTable@ /must/ be less than
--     or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxShaderGroupStride@
--
-- -   If @pCallableShaderBindingTable->buffer@ is non-sparse then it
--     /must/ be bound completely and contiguously to a single
--     'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   The @offset@ member of @pCallableShaderBindingTable@ /must/ be less
--     than the size of @pCallableShaderBindingTable->buffer@
--
-- -   The @offset@ member of @pCallableShaderBindingTable@ /must/ be a
--     multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupBaseAlignment@
--
-- -   @pCallableShaderBindingTable->offset@ +
--     @pCallableShaderBindingTable->size@ /must/ be less than or equal to
--     the size of @pCallableShaderBindingTable->buffer@
--
-- -   The @stride@ member of @pCallableShaderBindingTable@ /must/ be a
--     multiple of
--     'PhysicalDeviceRayTracingPropertiesKHR'::@shaderGroupHandleSize@
--
-- -   The @stride@ member of @pCallableShaderBindingTable@ /must/ be less
--     than or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxShaderGroupStride@
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR',
--     the @buffer@ member of @pHitShaderBindingTable@ /must/ not be
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR',
--     the @buffer@ member of @pHitShaderBindingTable@ /must/ not be
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR',
--     the @buffer@ member of @pHitShaderBindingTable@ /must/ not be
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_MISS_SHADERS_BIT_KHR',
--     the shader group handle identified by @pMissShaderBindingTable@
--     /must/ contain a valid miss shader
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR',
--     entries in @pHitShaderBindingTable@ accessed as a result of this
--     command in order to execute an any hit shader /must/ not be set to
--     zero
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR',
--     entries in @pHitShaderBindingTable@ accessed as a result of this
--     command in order to execute a closest hit shader /must/ not be set
--     to zero
--
-- -   If the currently bound ray tracing pipeline was created with @flags@
--     that included
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_INTERSECTION_SHADERS_BIT_KHR',
--     entries in @pHitShaderBindingTable@ accessed as a result of this
--     command in order to execute an intersection shader /must/ not be set
--     to zero
--
-- -   If @buffer@ is non-sparse then it /must/ be bound completely and
--     contiguously to a single 'Vulkan.Core10.Handles.DeviceMemory' object
--
-- -   @buffer@ /must/ have been created with the
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_INDIRECT_BUFFER_BIT'
--     bit set
--
-- -   @offset@ /must/ be a multiple of @4@
--
-- -   @commandBuffer@ /must/ not be a protected command buffer
--
-- -   (@offset@ + @sizeof@('TraceRaysIndirectCommandKHR')) /must/ be less
--     than or equal to the size of @buffer@
--
-- -   the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing-indirecttraceray ::rayTracingIndirectTraceRays>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pRaygenShaderBindingTable@ /must/ be a valid pointer to a valid
--     'StridedBufferRegionKHR' structure
--
-- -   @pMissShaderBindingTable@ /must/ be a valid pointer to a valid
--     'StridedBufferRegionKHR' structure
--
-- -   @pHitShaderBindingTable@ /must/ be a valid pointer to a valid
--     'StridedBufferRegionKHR' structure
--
-- -   @pCallableShaderBindingTable@ /must/ be a valid pointer to a valid
--     'StridedBufferRegionKHR' structure
--
-- -   @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   Both of @buffer@, and @commandBuffer@ /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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Compute                                                                                                               |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize', 'StridedBufferRegionKHR'
cmdTraceRaysIndirectKHR :: forall io
                         . (MonadIO io)
                        => -- | @commandBuffer@ is the command buffer into which the command will be
                           -- recorded.
                           CommandBuffer
                        -> -- | @pRaygenShaderBindingTable@ is a 'StridedBufferRegionKHR' that holds the
                           -- shader binding table data for the ray generation shader stage.
                           ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
                        -> -- | @pMissShaderBindingTable@ is a 'StridedBufferRegionKHR' that holds the
                           -- shader binding table data for the miss shader stage.
                           ("missShaderBindingTable" ::: StridedBufferRegionKHR)
                        -> -- | @pHitShaderBindingTable@ is a 'StridedBufferRegionKHR' that holds the
                           -- shader binding table data for the hit shader stage.
                           ("hitShaderBindingTable" ::: StridedBufferRegionKHR)
                        -> -- | @pCallableShaderBindingTable@ is a 'StridedBufferRegionKHR' that holds
                           -- the shader binding table data for the callable shader stage.
                           ("callableShaderBindingTable" ::: StridedBufferRegionKHR)
                        -> -- | @buffer@ is the buffer containing the trace ray parameters.
                           Buffer
                        -> -- | @offset@ is the byte offset into @buffer@ where parameters begin.
                           ("offset" ::: DeviceSize)
                        -> io ()
cmdTraceRaysIndirectKHR :: CommandBuffer
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> Buffer
-> ("dataSize" ::: Word64)
-> io ()
cmdTraceRaysIndirectKHR commandBuffer :: CommandBuffer
commandBuffer raygenShaderBindingTable :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
raygenShaderBindingTable missShaderBindingTable :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
missShaderBindingTable hitShaderBindingTable :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
hitShaderBindingTable callableShaderBindingTable :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
callableShaderBindingTable buffer :: Buffer
buffer offset :: "dataSize" ::: Word64
offset = 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 vkCmdTraceRaysIndirectKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> IO ())
vkCmdTraceRaysIndirectKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> Buffer
      -> ("dataSize" ::: Word64)
      -> IO ())
pVkCmdTraceRaysIndirectKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> IO ())
vkCmdTraceRaysIndirectKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> ("pRaygenShaderBindingTable"
          ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
      -> Buffer
      -> ("dataSize" ::: Word64)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> 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 "" "The function pointer for vkCmdTraceRaysIndirectKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdTraceRaysIndirectKHR' :: Ptr CommandBuffer_T
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Buffer
-> ("dataSize" ::: Word64)
-> IO ()
vkCmdTraceRaysIndirectKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Buffer
-> ("dataSize" ::: Word64)
-> IO ()
mkVkCmdTraceRaysIndirectKHR FunPtr
  (Ptr CommandBuffer_T
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> IO ())
vkCmdTraceRaysIndirectKHRPtr
  "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pRaygenShaderBindingTable <- ((("pRaygenShaderBindingTable"
   ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)))
-> ((("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall a b. (a -> b) -> a -> b
$ ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("raygenShaderBindingTable" ::: StridedBufferRegionKHR
raygenShaderBindingTable)
  "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pMissShaderBindingTable <- ((("pRaygenShaderBindingTable"
   ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)))
-> ((("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall a b. (a -> b) -> a -> b
$ ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("raygenShaderBindingTable" ::: StridedBufferRegionKHR
missShaderBindingTable)
  "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pHitShaderBindingTable <- ((("pRaygenShaderBindingTable"
   ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)))
-> ((("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall a b. (a -> b) -> a -> b
$ ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("raygenShaderBindingTable" ::: StridedBufferRegionKHR
hitShaderBindingTable)
  "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pCallableShaderBindingTable <- ((("pRaygenShaderBindingTable"
   ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("pRaygenShaderBindingTable"
       ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)))
-> ((("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("pRaygenShaderBindingTable"
      ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
forall a b. (a -> b) -> a -> b
$ ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("raygenShaderBindingTable" ::: StridedBufferRegionKHR
callableShaderBindingTable)
  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
$ Ptr CommandBuffer_T
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("pRaygenShaderBindingTable"
    ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Buffer
-> ("dataSize" ::: Word64)
-> IO ()
vkCmdTraceRaysIndirectKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pRaygenShaderBindingTable "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pMissShaderBindingTable "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pHitShaderBindingTable "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
pCallableShaderBindingTable (Buffer
buffer) ("dataSize" ::: Word64
offset)
  () -> 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" mkVkGetDeviceAccelerationStructureCompatibilityKHR
  :: FunPtr (Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result) -> Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result

-- | vkGetDeviceAccelerationStructureCompatibilityKHR - Check if a serialized
-- acceleration structure is compatible with the current device
--
-- = Description
--
-- This possible return values for
-- 'getDeviceAccelerationStructureCompatibilityKHR' are:
--
-- -   'Vulkan.Core10.Enums.Result.SUCCESS' is returned if an acceleration
--     structure serialized with @version@ as the version information is
--     compatible with @device@.
--
-- -   'Vulkan.Core10.Enums.Result.ERROR_INCOMPATIBLE_VERSION_KHR' is
--     returned if an acceleration structure serialized with @version@ as
--     the version information is not compatible with @device@.
--
-- == Valid Usage
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing rayTracing>
--     or
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayQuery rayQuery>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @version@ /must/ be a valid pointer to a valid
--     'AccelerationStructureVersionKHR' structure
--
-- == 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_INCOMPATIBLE_VERSION_KHR'
--
-- = See Also
--
-- 'AccelerationStructureVersionKHR', 'Vulkan.Core10.Handles.Device'
getDeviceAccelerationStructureCompatibilityKHR :: forall io
                                                . (MonadIO io)
                                               => -- | @device@ is the device to check the version against.
                                                  Device
                                               -> -- | @version@ points to the 'AccelerationStructureVersionKHR' version
                                                  -- information to check against the device.
                                                  AccelerationStructureVersionKHR
                                               -> io ()
getDeviceAccelerationStructureCompatibilityKHR :: Device -> AccelerationStructureVersionKHR -> io ()
getDeviceAccelerationStructureCompatibilityKHR device :: Device
device version :: AccelerationStructureVersionKHR
version = 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 vkGetDeviceAccelerationStructureCompatibilityKHRPtr :: FunPtr
  (Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result)
vkGetDeviceAccelerationStructureCompatibilityKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result)
pVkGetDeviceAccelerationStructureCompatibilityKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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 -> Ptr AccelerationStructureVersionKHR -> IO Result)
vkGetDeviceAccelerationStructureCompatibilityKHRPtr FunPtr
  (Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result)
-> FunPtr
     (Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> 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 "" "The function pointer for vkGetDeviceAccelerationStructureCompatibilityKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeviceAccelerationStructureCompatibilityKHR' :: Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result
vkGetDeviceAccelerationStructureCompatibilityKHR' = FunPtr
  (Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result)
-> Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result
mkVkGetDeviceAccelerationStructureCompatibilityKHR FunPtr
  (Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result)
vkGetDeviceAccelerationStructureCompatibilityKHRPtr
  Ptr AccelerationStructureVersionKHR
version' <- ((Ptr AccelerationStructureVersionKHR -> IO ()) -> IO ())
-> ContT () IO (Ptr AccelerationStructureVersionKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AccelerationStructureVersionKHR -> IO ()) -> IO ())
 -> ContT () IO (Ptr AccelerationStructureVersionKHR))
-> ((Ptr AccelerationStructureVersionKHR -> IO ()) -> IO ())
-> ContT () IO (Ptr AccelerationStructureVersionKHR)
forall a b. (a -> b) -> a -> b
$ AccelerationStructureVersionKHR
-> (Ptr AccelerationStructureVersionKHR -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AccelerationStructureVersionKHR
version)
  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
$ Ptr Device_T -> Ptr AccelerationStructureVersionKHR -> IO Result
vkGetDeviceAccelerationStructureCompatibilityKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) Ptr AccelerationStructureVersionKHR
version'
  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" mkVkCreateAccelerationStructureKHR
  :: FunPtr (Ptr Device_T -> Ptr AccelerationStructureCreateInfoKHR -> Ptr AllocationCallbacks -> Ptr AccelerationStructureKHR -> IO Result) -> Ptr Device_T -> Ptr AccelerationStructureCreateInfoKHR -> Ptr AllocationCallbacks -> Ptr AccelerationStructureKHR -> IO Result

-- | vkCreateAccelerationStructureKHR - Create a new acceleration structure
-- object
--
-- = Description
--
-- Similar to other objects in Vulkan, the acceleration structure creation
-- merely creates an object with a specific “shape”. The type and quantity
-- of geometry that can be built into an acceleration structure is
-- determined by the parameters of 'AccelerationStructureCreateInfoKHR'.
--
-- Populating the data in the object after allocating and binding memory is
-- done with commands such as 'cmdBuildAccelerationStructureKHR',
-- 'buildAccelerationStructureKHR', 'cmdCopyAccelerationStructureKHR', and
-- 'copyAccelerationStructureKHR'.
--
-- The input buffers passed to acceleration structure build commands will
-- be referenced by the implementation for the duration of the command.
-- After the command completes, the acceleration structure /may/ hold a
-- reference to any acceleration structure specified by an active instance
-- contained therein. Apart from this referencing, acceleration structures
-- /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 ray traversal.
--
-- == Valid Usage
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing rayTracing>
--     or
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayQuery rayQuery>
--     feature /must/ be enabled
--
-- -   If 'AccelerationStructureCreateInfoKHR'::@deviceAddress@ is not
--     zero, the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing-ascapturereplay rayTracingAccelerationStructureCaptureReplay>
--     feature /must/ be enabled
--
-- -   If @device@ was created with multiple physical devices, then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-bufferDeviceAddressMultiDevice bufferDeviceAddressMultiDevice>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pCreateInfo@ /must/ be a valid pointer to a valid
--     'AccelerationStructureCreateInfoKHR' structure
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pAccelerationStructure@ /must/ be a valid pointer to a
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' 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
--
-- 'AccelerationStructureCreateInfoKHR',
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device'
createAccelerationStructureKHR :: forall io
                                . (MonadIO io)
                               => -- | @device@ is the logical device that creates the buffer object.
                                  Device
                               -> -- | @pCreateInfo@ is a pointer to a 'AccelerationStructureCreateInfoKHR'
                                  -- structure containing parameters affecting creation of the acceleration
                                  -- structure.
                                  AccelerationStructureCreateInfoKHR
                               -> -- | @pAllocator@ controls host memory allocation as described in the
                                  -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                                  -- chapter.
                                  ("allocator" ::: Maybe AllocationCallbacks)
                               -> io (AccelerationStructureKHR)
createAccelerationStructureKHR :: Device
-> AccelerationStructureCreateInfoKHR
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io AccelerationStructureKHR
createAccelerationStructureKHR device :: Device
device createInfo :: AccelerationStructureCreateInfoKHR
createInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO AccelerationStructureKHR -> io AccelerationStructureKHR
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AccelerationStructureKHR -> io AccelerationStructureKHR)
-> (ContT AccelerationStructureKHR IO AccelerationStructureKHR
    -> IO AccelerationStructureKHR)
-> ContT AccelerationStructureKHR IO AccelerationStructureKHR
-> io AccelerationStructureKHR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT AccelerationStructureKHR IO AccelerationStructureKHR
-> IO AccelerationStructureKHR
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT AccelerationStructureKHR IO AccelerationStructureKHR
 -> io AccelerationStructureKHR)
-> ContT AccelerationStructureKHR IO AccelerationStructureKHR
-> io AccelerationStructureKHR
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateAccelerationStructureKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO Result)
vkCreateAccelerationStructureKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
      -> IO Result)
pVkCreateAccelerationStructureKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT AccelerationStructureKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT AccelerationStructureKHR IO ())
-> IO () -> ContT AccelerationStructureKHR IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO Result)
vkCreateAccelerationStructureKHRPtr FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> 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 "" "The function pointer for vkCreateAccelerationStructureKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateAccelerationStructureKHR' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO Result
vkCreateAccelerationStructureKHR' = FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO Result
mkVkCreateAccelerationStructureKHR FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO Result)
vkCreateAccelerationStructureKHRPtr
  "pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
pCreateInfo <- ((("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
  -> IO AccelerationStructureKHR)
 -> IO AccelerationStructureKHR)
-> ContT
     AccelerationStructureKHR
     IO
     ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
   -> IO AccelerationStructureKHR)
  -> IO AccelerationStructureKHR)
 -> ContT
      AccelerationStructureKHR
      IO
      ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR))
-> ((("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
     -> IO AccelerationStructureKHR)
    -> IO AccelerationStructureKHR)
-> ContT
     AccelerationStructureKHR
     IO
     ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
forall a b. (a -> b) -> a -> b
$ AccelerationStructureCreateInfoKHR
-> (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
    -> IO AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AccelerationStructureCreateInfoKHR
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT
     AccelerationStructureKHR
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks)
  -> IO AccelerationStructureKHR)
 -> IO AccelerationStructureKHR)
-> ContT
     AccelerationStructureKHR
     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 AccelerationStructureKHR)
  -> IO AccelerationStructureKHR)
 -> ContT
      AccelerationStructureKHR
      IO
      ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks)
     -> IO AccelerationStructureKHR)
    -> IO AccelerationStructureKHR)
-> ContT
     AccelerationStructureKHR
     IO
     ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks)
    -> IO AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructure <- ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
  -> IO AccelerationStructureKHR)
 -> IO AccelerationStructureKHR)
-> ContT
     AccelerationStructureKHR
     IO
     ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO AccelerationStructureKHR)
  -> IO AccelerationStructureKHR)
 -> ContT
      AccelerationStructureKHR
      IO
      ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR))
-> ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
     -> IO AccelerationStructureKHR)
    -> IO AccelerationStructureKHR)
-> ContT
     AccelerationStructureKHR
     IO
     ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a b. (a -> b) -> a -> b
$ IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> (("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
    -> IO ())
-> (("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
    -> IO AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int
-> IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a. Int -> IO (Ptr a)
callocBytes @AccelerationStructureKHR 8) ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT AccelerationStructureKHR IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT AccelerationStructureKHR IO Result)
-> IO Result -> ContT AccelerationStructureKHR IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO Result
vkCreateAccelerationStructureKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
pCreateInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructure)
  IO () -> ContT AccelerationStructureKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT AccelerationStructureKHR IO ())
-> IO () -> ContT AccelerationStructureKHR 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))
  AccelerationStructureKHR
pAccelerationStructure <- IO AccelerationStructureKHR
-> ContT AccelerationStructureKHR IO AccelerationStructureKHR
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO AccelerationStructureKHR
 -> ContT AccelerationStructureKHR IO AccelerationStructureKHR)
-> IO AccelerationStructureKHR
-> ContT AccelerationStructureKHR IO AccelerationStructureKHR
forall a b. (a -> b) -> a -> b
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureKHR "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructure
  AccelerationStructureKHR
-> ContT AccelerationStructureKHR IO AccelerationStructureKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AccelerationStructureKHR
 -> ContT AccelerationStructureKHR IO AccelerationStructureKHR)
-> AccelerationStructureKHR
-> ContT AccelerationStructureKHR IO AccelerationStructureKHR
forall a b. (a -> b) -> a -> b
$ (AccelerationStructureKHR
pAccelerationStructure)

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


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdBuildAccelerationStructureKHR
  :: FunPtr (Ptr CommandBuffer_T -> Word32 -> Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR) -> Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR) -> IO ()) -> Ptr CommandBuffer_T -> Word32 -> Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR) -> Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR) -> IO ()

-- | vkCmdBuildAccelerationStructureKHR - Build an acceleration structure
--
-- = Description
--
-- The 'cmdBuildAccelerationStructureKHR' command provides the ability to
-- initiate multiple acceleration structures builds, however there is no
-- ordering or synchronization implied between any of the individual
-- acceleration structure builds.
--
-- Note
--
-- This means that an application /cannot/ build a top-level acceleration
-- structure in the same 'cmdBuildAccelerationStructureKHR' call as the
-- associated bottom-level or instance acceleration structures are being
-- built. There also /cannot/ be any memory aliasing between any
-- acceleration structure memories or scratch memories being used by any of
-- the builds.
--
-- Accesses to the acceleration structure scratch buffers as identified by
-- the 'AccelerationStructureBuildGeometryInfoKHR'→@scratchData@ buffer
-- device addresses /must/ be
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-dependencies synchronized>
-- with the
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_ACCELERATION_STRUCTURE_BUILD_BIT_KHR'
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages pipeline stage>
-- and an
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-access-types access type>
-- of
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_ACCELERATION_STRUCTURE_READ_BIT_KHR'
-- or
-- 'Vulkan.Core10.Enums.AccessFlagBits.ACCESS_ACCELERATION_STRUCTURE_WRITE_BIT_KHR'.
--
-- == Valid Usage
--
-- -   Each element of @ppOffsetInfos@[i] /must/ be a valid pointer to an
--     array of @pInfos@[i].@geometryCount@
--     'AccelerationStructureBuildOffsetInfoKHR' structures
--
-- -   Each @pInfos@[i].@srcAccelerationStructure@ /must/ not refer to the
--     same acceleration structure as any
--     @pInfos@[i].@dstAccelerationStructure@ that is provided to the same
--     build command unless it is identical for an update
--
-- -   For each @pInfos@[i], @dstAccelerationStructure@ /must/ have been
--     created with compatible 'AccelerationStructureCreateInfoKHR' where
--     'AccelerationStructureCreateInfoKHR'::@type@ and
--     'AccelerationStructureCreateInfoKHR'::@flags@ are identical to
--     'AccelerationStructureBuildGeometryInfoKHR'::@type@ and
--     'AccelerationStructureBuildGeometryInfoKHR'::@flags@ respectively,
--     'AccelerationStructureBuildGeometryInfoKHR'::@geometryCount@ for
--     @dstAccelerationStructure@ are greater than or equal to the build
--     size, and each geometry in
--     'AccelerationStructureBuildGeometryInfoKHR'::@ppGeometries@ for
--     @dstAccelerationStructure@ has greater than or equal to the number
--     of vertices, indices, and AABBs,
--     'AccelerationStructureGeometryTrianglesDataKHR'::@transformData@ is
--     both 0 or both non-zero, and all other parameters are the same
--
-- -   For each @pInfos@[i], if @update@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE', then objects that were
--     previously active for that acceleration structure /must/ not be made
--     inactive as per
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#acceleration-structure-inactive-prims ???>
--
-- -   For each @pInfos@[i], if @update@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE', then objects that were
--     previously inactive for that acceleration structure /must/ not be
--     made active as per
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#acceleration-structure-inactive-prims ???>
--
-- -   Any acceleration structure instance in any top level build in this
--     command /must/ not reference any bottom level acceleration structure
--     built by this command
--
-- -   There /must/ not be any
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-memory-aliasing memory aliasing>
--     between the scratch memories that are provided in all the
--     @pInfos@[i].@scratchData@ memories for the acceleration structure
--     builds
--
-- -   There /must/ not be any
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-memory-aliasing memory aliasing>
--     between memory bound to any top level, bottom level, or instance
--     acceleration structure accessed by this command
--
-- -   If @update@ is 'Vulkan.Core10.FundamentalTypes.FALSE', all addresses
--     between @pInfos@[i].@scratchData@ and @pInfos@[i].@scratchData@ + N
--     - 1 /must/ be in the buffer device address range of the same buffer,
--     where N is given by the @size@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'getAccelerationStructureMemoryRequirementsKHR' with
--     'AccelerationStructureMemoryRequirementsInfoKHR'::@accelerationStructure@
--     set to @pInfos@[i].@dstAccelerationStructure@ and
--     'AccelerationStructureMemoryRequirementsInfoKHR'::@type@ set to
--     'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR'
--
-- -   If @update@ is 'Vulkan.Core10.FundamentalTypes.TRUE', all addresses
--     between @pInfos@[i].@scratchData@ and @pInfos@[i].@scratchData@ + N
--     - 1 /must/ be in the buffer device address range of the same buffer,
--     where N is given by the @size@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'getAccelerationStructureMemoryRequirementsKHR' with
--     'AccelerationStructureMemoryRequirementsInfoKHR'::@accelerationStructure@
--     set to @pInfos@[i].@dstAccelerationStructure@ and
--     'AccelerationStructureMemoryRequirementsInfoKHR'::@type@ set to
--     'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR'
--
-- -   The buffer from which the buffer device address
--     @pInfos@[i].@scratchData@ is queried /must/ have been created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_RAY_TRACING_BIT_KHR'
--     usage flag
--
-- -   All 'DeviceOrHostAddressKHR' or 'DeviceOrHostAddressConstKHR'
--     referenced by this command /must/ contain valid device addresses for
--     a buffer bound to device memory. If the buffer is non-sparse then it
--     /must/ be bound completely and contiguously to a single
--     VkDeviceMemory object
--
-- -   All 'Vulkan.Extensions.Handles.AccelerationStructureKHR' objects
--     referenced by this command /must/ be bound to device memory
--
-- -   The
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--     structure /must/ not be included in the @pNext@ chain of any of the
--     provided 'AccelerationStructureBuildGeometryInfoKHR' structures
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pInfos@ /must/ be a valid pointer to an array of @infoCount@ valid
--     'AccelerationStructureBuildGeometryInfoKHR' structures
--
-- -   @ppOffsetInfos@ /must/ be a valid pointer to an array of @infoCount@
--     'AccelerationStructureBuildOffsetInfoKHR' structures
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   @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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Compute                                                                                                               |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'AccelerationStructureBuildGeometryInfoKHR',
-- 'AccelerationStructureBuildOffsetInfoKHR',
-- 'Vulkan.Core10.Handles.CommandBuffer'
cmdBuildAccelerationStructureKHR :: forall io
                                  . (MonadIO io)
                                 => -- | @commandBuffer@ is the command buffer into which the command will be
                                    -- recorded.
                                    CommandBuffer
                                 -> -- | @pInfos@ is an array of @infoCount@
                                    -- 'AccelerationStructureBuildGeometryInfoKHR' structures defining the
                                    -- geometry used to build each acceleration structure.
                                    ("infos" ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
                                 -> -- | @ppOffsetInfos@ is an array of @infoCount@ pointers to arrays of
                                    -- 'AccelerationStructureBuildOffsetInfoKHR' structures. Each
                                    -- @ppOffsetInfos@[i] is an array of @pInfos@[i].@geometryCount@
                                    -- 'AccelerationStructureBuildOffsetInfoKHR' structures defining dynamic
                                    -- offsets to the addresses where geometry data is stored, as defined by
                                    -- @pInfos@[i].
                                    ("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR)
                                 -> io ()
cmdBuildAccelerationStructureKHR :: CommandBuffer
-> ("infos"
    ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ("offsetInfos"
    ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> io ()
cmdBuildAccelerationStructureKHR commandBuffer :: CommandBuffer
commandBuffer infos :: "infos"
::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
infos offsetInfos :: "offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR
offsetInfos = 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 vkCmdBuildAccelerationStructureKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO ())
vkCmdBuildAccelerationStructureKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pInfos"
          ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
      -> ("ppOffsetInfos"
          ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
      -> IO ())
pVkCmdBuildAccelerationStructureKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO ())
vkCmdBuildAccelerationStructureKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pInfos"
          ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
      -> ("ppOffsetInfos"
          ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> 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 "" "The function pointer for vkCmdBuildAccelerationStructureKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBuildAccelerationStructureKHR' :: Ptr CommandBuffer_T
-> ("bindInfoCount" ::: Word32)
-> ("pInfos"
    ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ("ppOffsetInfos"
    ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> IO ()
vkCmdBuildAccelerationStructureKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO ())
-> Ptr CommandBuffer_T
-> ("bindInfoCount" ::: Word32)
-> ("pInfos"
    ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ("ppOffsetInfos"
    ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> IO ()
mkVkCmdBuildAccelerationStructureKHR FunPtr
  (Ptr CommandBuffer_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO ())
vkCmdBuildAccelerationStructureKHRPtr
  let pInfosLength :: Int
pInfosLength = ("infos"
 ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("infos"
  ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
 -> Int)
-> ("infos"
    ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> Int
forall a b. (a -> b) -> a -> b
$ ("infos"
::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
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
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length (("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR)
 -> Int)
-> ("offsetInfos"
    ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> Int
forall a b. (a -> b) -> a -> b
$ ("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR
offsetInfos)) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pInfosLength) (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 "" "ppOffsetInfos and pInfos must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
pPInfos <- ((Ptr (AccelerationStructureBuildGeometryInfoKHR Any) -> IO ())
 -> IO ())
-> ContT
     () IO (Ptr (AccelerationStructureBuildGeometryInfoKHR Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AccelerationStructureBuildGeometryInfoKHR Any) -> IO ())
  -> IO ())
 -> ContT
      () IO (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)))
-> ((Ptr (AccelerationStructureBuildGeometryInfoKHR Any) -> IO ())
    -> IO ())
-> ContT
     () IO (Ptr (AccelerationStructureBuildGeometryInfoKHR Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr (AccelerationStructureBuildGeometryInfoKHR Any) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AccelerationStructureBuildGeometryInfoKHR _) ((("infos"
 ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("infos"
::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
infos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 72) 8
  (Int
 -> SomeStruct AccelerationStructureBuildGeometryInfoKHR
 -> ContT () IO ())
-> ("infos"
    ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AccelerationStructureBuildGeometryInfoKHR
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 (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> SomeStruct AccelerationStructureBuildGeometryInfoKHR
-> IO ()
-> IO ()
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
-> "pInfos"
   ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
pPInfos Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
-> Int -> Ptr (AccelerationStructureBuildGeometryInfoKHR _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (72 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AccelerationStructureBuildGeometryInfoKHR _))) (SomeStruct AccelerationStructureBuildGeometryInfoKHR
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 (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
infos)
  "ppOffsetInfos"
::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)
pPpOffsetInfos <- ((("ppOffsetInfos"
   ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
  -> IO ())
 -> IO ())
-> ContT
     ()
     IO
     ("ppOffsetInfos"
      ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("ppOffsetInfos"
    ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO ())
  -> IO ())
 -> ContT
      ()
      IO
      ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)))
-> ((("ppOffsetInfos"
      ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
     -> IO ())
    -> IO ())
-> ContT
     ()
     IO
     ("ppOffsetInfos"
      ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("ppOffsetInfos"
     ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
    -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr AccelerationStructureBuildOffsetInfoKHR) ((("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length ("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR
offsetInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
  (Int -> AccelerationStructureBuildOffsetInfoKHR -> ContT () IO ())
-> ("offsetInfos"
    ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AccelerationStructureBuildOffsetInfoKHR
e -> do
    Ptr AccelerationStructureBuildOffsetInfoKHR
ppOffsetInfos <- ((Ptr AccelerationStructureBuildOffsetInfoKHR -> IO ()) -> IO ())
-> ContT () IO (Ptr AccelerationStructureBuildOffsetInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AccelerationStructureBuildOffsetInfoKHR -> IO ()) -> IO ())
 -> ContT () IO (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> ((Ptr AccelerationStructureBuildOffsetInfoKHR -> IO ())
    -> IO ())
-> ContT () IO (Ptr AccelerationStructureBuildOffsetInfoKHR)
forall a b. (a -> b) -> a -> b
$ AccelerationStructureBuildOffsetInfoKHR
-> (Ptr AccelerationStructureBuildOffsetInfoKHR -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AccelerationStructureBuildOffsetInfoKHR
e)
    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
$ ("ppOffsetInfos"
 ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> Ptr AccelerationStructureBuildOffsetInfoKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("ppOffsetInfos"
::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)
pPpOffsetInfos ("ppOffsetInfos"
 ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> Int
-> "ppOffsetInfos"
   ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)) Ptr AccelerationStructureBuildOffsetInfoKHR
ppOffsetInfos) ("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR
offsetInfos)
  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
$ Ptr CommandBuffer_T
-> ("bindInfoCount" ::: Word32)
-> ("pInfos"
    ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ("ppOffsetInfos"
    ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> IO ()
vkCmdBuildAccelerationStructureKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pInfosLength :: Word32)) (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
-> "pInfos"
   ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
pPInfos)) ("ppOffsetInfos"
::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)
pPpOffsetInfos)
  () -> 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" mkVkCmdBuildAccelerationStructureIndirectKHR
  :: FunPtr (Ptr CommandBuffer_T -> Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR) -> Buffer -> DeviceSize -> Word32 -> IO ()) -> Ptr CommandBuffer_T -> Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR) -> Buffer -> DeviceSize -> Word32 -> IO ()

-- | vkCmdBuildAccelerationStructureIndirectKHR - Build an acceleration
-- structure with some parameters provided on the device
--
-- == Valid Usage
--
-- -   All 'DeviceOrHostAddressKHR' or 'DeviceOrHostAddressConstKHR'
--     referenced by this command /must/ contain valid device addresses for
--     a buffer bound to device memory. If the buffer is non-sparse then it
--     /must/ be bound completely and contiguously to a single
--     VkDeviceMemory object
--
-- -   All 'Vulkan.Extensions.Handles.AccelerationStructureKHR' objects
--     referenced by this command /must/ be bound to device memory
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing-indirectasbuild ::rayTracingIndirectAccelerationStructureBuild>
--     feature /must/ be enabled
--
-- -   The
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--     structure /must/ not be included in the @pNext@ chain of any of the
--     provided 'AccelerationStructureBuildGeometryInfoKHR' structures
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pInfo@ /must/ be a valid pointer to a valid
--     'AccelerationStructureBuildGeometryInfoKHR' structure
--
-- -   @indirectBuffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer'
--     handle
--
-- -   @commandBuffer@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle recording state>
--
-- -   The 'Vulkan.Core10.Handles.CommandPool' that @commandBuffer@ was
--     allocated from /must/ support compute operations
--
-- -   This command /must/ only be called outside of a render pass instance
--
-- -   Both of @commandBuffer@, and @indirectBuffer@ /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#VkQueueFlagBits Supported Queue Types> | <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-types Pipeline Type> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | Primary                                                                                                                    | Outside                                                                                                                | Compute                                                                                                               |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        |                                                                                                                       |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'AccelerationStructureBuildGeometryInfoKHR',
-- 'Vulkan.Core10.Handles.Buffer', 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize'
cmdBuildAccelerationStructureIndirectKHR :: forall a io
                                          . (Extendss AccelerationStructureBuildGeometryInfoKHR a, PokeChain a, MonadIO io)
                                         => -- | @commandBuffer@ is the command buffer into which the command will be
                                            -- recorded.
                                            CommandBuffer
                                         -> -- | @pInfo@ is a pointer to a 'AccelerationStructureBuildGeometryInfoKHR'
                                            -- structure defining the geometry used to build the acceleration
                                            -- structure.
                                            (AccelerationStructureBuildGeometryInfoKHR a)
                                         -> -- | @indirectBuffer@ is the 'Vulkan.Core10.Handles.Buffer' containing
                                            -- @pInfo->geometryCount@ 'AccelerationStructureBuildOffsetInfoKHR'
                                            -- structures defining dynamic offsets to the addresses where geometry data
                                            -- is stored, as defined by @pInfo@.
                                            ("indirectBuffer" ::: Buffer)
                                         -> -- | @indirectOffset@ is the byte offset into @indirectBuffer@ where offset
                                            -- parameters begin.
                                            ("indirectOffset" ::: DeviceSize)
                                         -> -- No documentation found for Nested "vkCmdBuildAccelerationStructureIndirectKHR" "indirectStride"
                                            ("indirectStride" ::: Word32)
                                         -> io ()
cmdBuildAccelerationStructureIndirectKHR :: CommandBuffer
-> AccelerationStructureBuildGeometryInfoKHR a
-> Buffer
-> ("dataSize" ::: Word64)
-> ("bindInfoCount" ::: Word32)
-> io ()
cmdBuildAccelerationStructureIndirectKHR commandBuffer :: CommandBuffer
commandBuffer info :: AccelerationStructureBuildGeometryInfoKHR a
info indirectBuffer :: Buffer
indirectBuffer indirectOffset :: "dataSize" ::: Word64
indirectOffset indirectStride :: "bindInfoCount" ::: Word32
indirectStride = 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 vkCmdBuildAccelerationStructureIndirectKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
vkCmdBuildAccelerationStructureIndirectKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfos"
          ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
      -> Buffer
      -> ("dataSize" ::: Word64)
      -> ("bindInfoCount" ::: Word32)
      -> IO ())
pVkCmdBuildAccelerationStructureIndirectKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  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
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
vkCmdBuildAccelerationStructureIndirectKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> ("pInfos"
          ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
      -> Buffer
      -> ("dataSize" ::: Word64)
      -> ("bindInfoCount" ::: Word32)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> ("bindInfoCount" ::: Word32)
   -> 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 "" "The function pointer for vkCmdBuildAccelerationStructureIndirectKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdBuildAccelerationStructureIndirectKHR' :: Ptr CommandBuffer_T
-> ("pInfos"
    ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> Buffer
-> ("dataSize" ::: Word64)
-> ("bindInfoCount" ::: Word32)
-> IO ()
vkCmdBuildAccelerationStructureIndirectKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
-> Ptr CommandBuffer_T
-> ("pInfos"
    ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> Buffer
-> ("dataSize" ::: Word64)
-> ("bindInfoCount" ::: Word32)
-> IO ()
mkVkCmdBuildAccelerationStructureIndirectKHR FunPtr
  (Ptr CommandBuffer_T
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> Buffer
   -> ("dataSize" ::: Word64)
   -> ("bindInfoCount" ::: Word32)
   -> IO ())
vkCmdBuildAccelerationStructureIndirectKHRPtr
  Ptr (AccelerationStructureBuildGeometryInfoKHR a)
pInfo <- ((Ptr (AccelerationStructureBuildGeometryInfoKHR a) -> IO ())
 -> IO ())
-> ContT () IO (Ptr (AccelerationStructureBuildGeometryInfoKHR a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AccelerationStructureBuildGeometryInfoKHR a) -> IO ())
  -> IO ())
 -> ContT () IO (Ptr (AccelerationStructureBuildGeometryInfoKHR a)))
-> ((Ptr (AccelerationStructureBuildGeometryInfoKHR a) -> IO ())
    -> IO ())
-> ContT () IO (Ptr (AccelerationStructureBuildGeometryInfoKHR a))
forall a b. (a -> b) -> a -> b
$ AccelerationStructureBuildGeometryInfoKHR a
-> (Ptr (AccelerationStructureBuildGeometryInfoKHR a) -> IO ())
-> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AccelerationStructureBuildGeometryInfoKHR a
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
$ Ptr CommandBuffer_T
-> ("pInfos"
    ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> Buffer
-> ("dataSize" ::: Word64)
-> ("bindInfoCount" ::: Word32)
-> IO ()
vkCmdBuildAccelerationStructureIndirectKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (Ptr (AccelerationStructureBuildGeometryInfoKHR a)
-> "pInfos"
   ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (AccelerationStructureBuildGeometryInfoKHR a)
pInfo) (Buffer
indirectBuffer) ("dataSize" ::: Word64
indirectOffset) ("bindInfoCount" ::: Word32
indirectStride)
  () -> 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" mkVkBuildAccelerationStructureKHR
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR) -> Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR) -> IO Result) -> Ptr Device_T -> Word32 -> Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR) -> Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR) -> IO Result

-- | vkBuildAccelerationStructureKHR - Build an acceleration structure on the
-- host
--
-- = Parameters
--
-- This command fulfills the same task as
-- 'cmdBuildAccelerationStructureKHR' but executed by the host.
--
-- = Description
--
-- -   @device@ is the 'Vulkan.Core10.Handles.Device' for which the
--     acceleration structures are being built.
--
-- -   @infoCount@ is the number of acceleration structures to build. It
--     specifies the number of the @pInfos@ structures and @ppOffsetInfos@
--     pointers that /must/ be provided.
--
-- -   @pInfos@ is a pointer to an array of @infoCount@
--     'AccelerationStructureBuildGeometryInfoKHR' structures defining the
--     geometry used to build each acceleration structure.
--
-- -   @ppOffsetInfos@ is an array of @infoCount@ pointers to arrays of
--     'AccelerationStructureBuildOffsetInfoKHR' structures. Each
--     @ppOffsetInfos@[i] is an array of @pInfos@[i].@geometryCount@
--     'AccelerationStructureBuildOffsetInfoKHR' structures defining
--     dynamic offsets to the addresses where geometry data is stored, as
--     defined by @pInfos@[i].
--
-- The 'buildAccelerationStructureKHR' command provides the ability to
-- initiate multiple acceleration structures builds, however there is no
-- ordering or synchronization implied between any of the individual
-- acceleration structure builds.
--
-- Note
--
-- This means that an application /cannot/ build a top-level acceleration
-- structure in the same 'buildAccelerationStructureKHR' call as the
-- associated bottom-level or instance acceleration structures are being
-- built. There also /cannot/ be any memory aliasing between any
-- acceleration structure memories or scratch memories being used by any of
-- the builds.
--
-- If the
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
-- structure is included in the @pNext@ chain of any
-- 'AccelerationStructureBuildGeometryInfoKHR' structure, the operation of
-- this command is /deferred/, as defined in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#deferred-host-operations Deferred Host Operations>
-- chapter.
--
-- == Valid Usage
--
-- -   Each element of @ppOffsetInfos@[i] /must/ be a valid pointer to an
--     array of @pInfos@[i].@geometryCount@
--     'AccelerationStructureBuildOffsetInfoKHR' structures
--
-- -   Each @pInfos@[i].@srcAccelerationStructure@ /must/ not refer to the
--     same acceleration structure as any
--     @pInfos@[i].@dstAccelerationStructure@ that is provided to the same
--     build command unless it is identical for an update
--
-- -   For each @pInfos@[i], @dstAccelerationStructure@ /must/ have been
--     created with compatible 'AccelerationStructureCreateInfoKHR' where
--     'AccelerationStructureCreateInfoKHR'::@type@ and
--     'AccelerationStructureCreateInfoKHR'::@flags@ are identical to
--     'AccelerationStructureBuildGeometryInfoKHR'::@type@ and
--     'AccelerationStructureBuildGeometryInfoKHR'::@flags@ respectively,
--     'AccelerationStructureBuildGeometryInfoKHR'::@geometryCount@ for
--     @dstAccelerationStructure@ are greater than or equal to the build
--     size, and each geometry in
--     'AccelerationStructureBuildGeometryInfoKHR'::@ppGeometries@ for
--     @dstAccelerationStructure@ has greater than or equal to the number
--     of vertices, indices, and AABBs,
--     'AccelerationStructureGeometryTrianglesDataKHR'::@transformData@ is
--     both 0 or both non-zero, and all other parameters are the same
--
-- -   For each @pInfos@[i], if @update@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE', then objects that were
--     previously active for that acceleration structure /must/ not be made
--     inactive as per
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#acceleration-structure-inactive-prims ???>
--
-- -   For each @pInfos@[i], if @update@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE', then objects that were
--     previously inactive for that acceleration structure /must/ not be
--     made active as per
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#acceleration-structure-inactive-prims ???>
--
-- -   Any acceleration structure instance in any top level build in this
--     command /must/ not reference any bottom level acceleration structure
--     built by this command
--
-- -   There /must/ not be any
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-memory-aliasing memory aliasing>
--     between the scratch memories that are provided in all the
--     @pInfos@[i].@scratchData@ memories for the acceleration structure
--     builds
--
-- -   There /must/ not be any
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-memory-aliasing memory aliasing>
--     between memory bound to any top level, bottom level, or instance
--     acceleration structure accessed by this command
--
-- -   All 'DeviceOrHostAddressKHR' or 'DeviceOrHostAddressConstKHR'
--     referenced by this command /must/ contain valid host addresses
--
-- -   All 'Vulkan.Extensions.Handles.AccelerationStructureKHR' objects
--     referenced by this command /must/ be bound to host-visible memory
--
-- -   The
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing-hostascmds ::rayTracingHostAccelerationStructureCommands>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pInfos@ /must/ be a valid pointer to an array of @infoCount@ valid
--     'AccelerationStructureBuildGeometryInfoKHR' structures
--
-- -   @ppOffsetInfos@ /must/ be a valid pointer to an array of @infoCount@
--     'AccelerationStructureBuildOffsetInfoKHR' structures
--
-- -   @infoCount@ /must/ be greater than @0@
--
-- == 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
--
-- 'AccelerationStructureBuildGeometryInfoKHR',
-- 'AccelerationStructureBuildOffsetInfoKHR',
-- 'Vulkan.Core10.Handles.Device'
buildAccelerationStructureKHR :: forall io
                               . (MonadIO io)
                              => -- No documentation found for Nested "vkBuildAccelerationStructureKHR" "device"
                                 Device
                              -> -- No documentation found for Nested "vkBuildAccelerationStructureKHR" "pInfos"
                                 ("infos" ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
                              -> -- No documentation found for Nested "vkBuildAccelerationStructureKHR" "ppOffsetInfos"
                                 ("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR)
                              -> io (Result)
buildAccelerationStructureKHR :: Device
-> ("infos"
    ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ("offsetInfos"
    ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> io Result
buildAccelerationStructureKHR device :: Device
device infos :: "infos"
::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
infos offsetInfos :: "offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR
offsetInfos = 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 vkBuildAccelerationStructureKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO Result)
vkBuildAccelerationStructureKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pInfos"
          ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
      -> ("ppOffsetInfos"
          ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
      -> IO Result)
pVkBuildAccelerationStructureKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  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
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO Result)
vkBuildAccelerationStructureKHRPtr FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("bindInfoCount" ::: Word32)
      -> ("pInfos"
          ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
      -> ("ppOffsetInfos"
          ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> 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 "" "The function pointer for vkBuildAccelerationStructureKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkBuildAccelerationStructureKHR' :: Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pInfos"
    ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ("ppOffsetInfos"
    ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> IO Result
vkBuildAccelerationStructureKHR' = FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO Result)
-> Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pInfos"
    ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ("ppOffsetInfos"
    ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> IO Result
mkVkBuildAccelerationStructureKHR FunPtr
  (Ptr Device_T
   -> ("bindInfoCount" ::: Word32)
   -> ("pInfos"
       ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
   -> ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO Result)
vkBuildAccelerationStructureKHRPtr
  let pInfosLength :: Int
pInfosLength = ("infos"
 ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("infos"
  ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
 -> Int)
-> ("infos"
    ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> Int
forall a b. (a -> b) -> a -> b
$ ("infos"
::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
infos)
  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 ((("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length (("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR)
 -> Int)
-> ("offsetInfos"
    ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> Int
forall a b. (a -> b) -> a -> b
$ ("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR
offsetInfos)) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pInfosLength) (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 "" "ppOffsetInfos and pInfos must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
pPInfos <- ((Ptr (AccelerationStructureBuildGeometryInfoKHR Any) -> IO Result)
 -> IO Result)
-> ContT
     Result IO (Ptr (AccelerationStructureBuildGeometryInfoKHR Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
   -> IO Result)
  -> IO Result)
 -> ContT
      Result IO (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)))
-> ((Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
     -> IO Result)
    -> IO Result)
-> ContT
     Result IO (Ptr (AccelerationStructureBuildGeometryInfoKHR Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
    -> IO Result)
-> IO Result
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(AccelerationStructureBuildGeometryInfoKHR _) ((("infos"
 ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("infos"
::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
infos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 72) 8
  (Int
 -> SomeStruct AccelerationStructureBuildGeometryInfoKHR
 -> ContT Result IO ())
-> ("infos"
    ::: Vector (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ContT Result IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct AccelerationStructureBuildGeometryInfoKHR
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 (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> SomeStruct AccelerationStructureBuildGeometryInfoKHR
-> IO Result
-> IO Result
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
-> "pInfos"
   ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
pPInfos Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
-> Int -> Ptr (AccelerationStructureBuildGeometryInfoKHR _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (72 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (AccelerationStructureBuildGeometryInfoKHR _))) (SomeStruct AccelerationStructureBuildGeometryInfoKHR
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 (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
infos)
  "ppOffsetInfos"
::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)
pPpOffsetInfos <- ((("ppOffsetInfos"
   ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
  -> IO Result)
 -> IO Result)
-> ContT
     Result
     IO
     ("ppOffsetInfos"
      ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("ppOffsetInfos"
    ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
   -> IO Result)
  -> IO Result)
 -> ContT
      Result
      IO
      ("ppOffsetInfos"
       ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)))
-> ((("ppOffsetInfos"
      ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
     -> IO Result)
    -> IO Result)
-> ContT
     Result
     IO
     ("ppOffsetInfos"
      ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("ppOffsetInfos"
     ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
    -> IO Result)
-> IO Result
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr AccelerationStructureBuildOffsetInfoKHR) ((("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length ("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR
offsetInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
  (Int
 -> AccelerationStructureBuildOffsetInfoKHR -> ContT Result IO ())
-> ("offsetInfos"
    ::: Vector AccelerationStructureBuildOffsetInfoKHR)
-> ContT Result IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AccelerationStructureBuildOffsetInfoKHR
e -> do
    Ptr AccelerationStructureBuildOffsetInfoKHR
ppOffsetInfos <- ((Ptr AccelerationStructureBuildOffsetInfoKHR -> IO Result)
 -> IO Result)
-> ContT Result IO (Ptr AccelerationStructureBuildOffsetInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AccelerationStructureBuildOffsetInfoKHR -> IO Result)
  -> IO Result)
 -> ContT Result IO (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> ((Ptr AccelerationStructureBuildOffsetInfoKHR -> IO Result)
    -> IO Result)
-> ContT Result IO (Ptr AccelerationStructureBuildOffsetInfoKHR)
forall a b. (a -> b) -> a -> b
$ AccelerationStructureBuildOffsetInfoKHR
-> (Ptr AccelerationStructureBuildOffsetInfoKHR -> IO Result)
-> IO Result
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AccelerationStructureBuildOffsetInfoKHR
e)
    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
$ ("ppOffsetInfos"
 ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> Ptr AccelerationStructureBuildOffsetInfoKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("ppOffsetInfos"
::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)
pPpOffsetInfos ("ppOffsetInfos"
 ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> Int
-> "ppOffsetInfos"
   ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)) Ptr AccelerationStructureBuildOffsetInfoKHR
ppOffsetInfos) ("offsetInfos" ::: Vector AccelerationStructureBuildOffsetInfoKHR
offsetInfos)
  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
$ Ptr Device_T
-> ("bindInfoCount" ::: Word32)
-> ("pInfos"
    ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR))
-> ("ppOffsetInfos"
    ::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR))
-> IO Result
vkBuildAccelerationStructureKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pInfosLength :: Word32)) (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
-> "pInfos"
   ::: Ptr (SomeStruct AccelerationStructureBuildGeometryInfoKHR)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (AccelerationStructureBuildGeometryInfoKHR Any)
pPInfos)) ("ppOffsetInfos"
::: Ptr (Ptr AccelerationStructureBuildOffsetInfoKHR)
pPpOffsetInfos)
  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" mkVkGetAccelerationStructureDeviceAddressKHR
  :: FunPtr (Ptr Device_T -> Ptr AccelerationStructureDeviceAddressInfoKHR -> IO DeviceAddress) -> Ptr Device_T -> Ptr AccelerationStructureDeviceAddressInfoKHR -> IO DeviceAddress

-- | vkGetAccelerationStructureDeviceAddressKHR - Query an address of a
-- acceleration structure
--
-- = Description
--
-- The 64-bit return value is an address of the acceleration structure,
-- which can be used for device and shader operations that involve
-- acceleration structures, such as ray traversal and acceleration
-- structure building.
--
-- If the acceleration structure was created with a non-zero value of
-- 'AccelerationStructureCreateInfoKHR'::@deviceAddress@ the return value
-- will be the same address.
--
-- == Valid Usage
--
-- -   If @device@ was created with multiple physical devices, then the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-bufferDeviceAddressMultiDevice bufferDeviceAddressMultiDevice>
--     feature /must/ be enabled
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pInfo@ /must/ be a valid pointer to a valid
--     'AccelerationStructureDeviceAddressInfoKHR' structure
--
-- = See Also
--
-- 'AccelerationStructureDeviceAddressInfoKHR',
-- 'Vulkan.Core10.Handles.Device'
getAccelerationStructureDeviceAddressKHR :: forall io
                                          . (MonadIO io)
                                         => -- | @device@ is the logical device that the accelerationStructure was
                                            -- created on.
                                            Device
                                         -> -- | @pInfo@ is a pointer to a 'AccelerationStructureDeviceAddressInfoKHR'
                                            -- structure specifying the acceleration structure to retrieve an address
                                            -- for.
                                            AccelerationStructureDeviceAddressInfoKHR
                                         -> io (DeviceAddress)
getAccelerationStructureDeviceAddressKHR :: Device
-> AccelerationStructureDeviceAddressInfoKHR
-> io ("dataSize" ::: Word64)
getAccelerationStructureDeviceAddressKHR device :: Device
device info :: AccelerationStructureDeviceAddressInfoKHR
info = IO ("dataSize" ::: Word64) -> io ("dataSize" ::: Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("dataSize" ::: Word64) -> io ("dataSize" ::: Word64))
-> (ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64)
    -> IO ("dataSize" ::: Word64))
-> ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64)
-> io ("dataSize" ::: Word64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64)
-> IO ("dataSize" ::: Word64)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64)
 -> io ("dataSize" ::: Word64))
-> ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64)
-> io ("dataSize" ::: Word64)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetAccelerationStructureDeviceAddressKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
   -> IO ("dataSize" ::: Word64))
vkGetAccelerationStructureDeviceAddressKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
      -> IO ("dataSize" ::: Word64))
pVkGetAccelerationStructureDeviceAddressKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT ("dataSize" ::: Word64) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("dataSize" ::: Word64) IO ())
-> IO () -> ContT ("dataSize" ::: Word64) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
   -> IO ("dataSize" ::: Word64))
vkGetAccelerationStructureDeviceAddressKHRPtr FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
   -> IO ("dataSize" ::: Word64))
-> FunPtr
     (Ptr Device_T
      -> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
      -> IO ("dataSize" ::: Word64))
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
   -> IO ("dataSize" ::: Word64))
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 "" "The function pointer for vkGetAccelerationStructureDeviceAddressKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetAccelerationStructureDeviceAddressKHR' :: Ptr Device_T
-> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> IO ("dataSize" ::: Word64)
vkGetAccelerationStructureDeviceAddressKHR' = FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
   -> IO ("dataSize" ::: Word64))
-> Ptr Device_T
-> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> IO ("dataSize" ::: Word64)
mkVkGetAccelerationStructureDeviceAddressKHR FunPtr
  (Ptr Device_T
   -> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
   -> IO ("dataSize" ::: Word64))
vkGetAccelerationStructureDeviceAddressKHRPtr
  "pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
pInfo <- ((("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
  -> IO ("dataSize" ::: Word64))
 -> IO ("dataSize" ::: Word64))
-> ContT
     ("dataSize" ::: Word64)
     IO
     ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
   -> IO ("dataSize" ::: Word64))
  -> IO ("dataSize" ::: Word64))
 -> ContT
      ("dataSize" ::: Word64)
      IO
      ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR))
-> ((("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
     -> IO ("dataSize" ::: Word64))
    -> IO ("dataSize" ::: Word64))
-> ContT
     ("dataSize" ::: Word64)
     IO
     ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
forall a b. (a -> b) -> a -> b
$ AccelerationStructureDeviceAddressInfoKHR
-> (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
    -> IO ("dataSize" ::: Word64))
-> IO ("dataSize" ::: Word64)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AccelerationStructureDeviceAddressInfoKHR
info)
  "dataSize" ::: Word64
r <- IO ("dataSize" ::: Word64)
-> ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("dataSize" ::: Word64)
 -> ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64))
-> IO ("dataSize" ::: Word64)
-> ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64)
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> IO ("dataSize" ::: Word64)
vkGetAccelerationStructureDeviceAddressKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
pInfo
  ("dataSize" ::: Word64)
-> ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("dataSize" ::: Word64)
 -> ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64))
-> ("dataSize" ::: Word64)
-> ContT ("dataSize" ::: Word64) IO ("dataSize" ::: Word64)
forall a b. (a -> b) -> a -> b
$ ("dataSize" ::: Word64
r)


-- | VkRayTracingShaderGroupCreateInfoKHR - Structure specifying shaders in a
-- shader group
--
-- == Valid Usage
--
-- -   If @type@ is 'RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR' then
--     @generalShader@ /must/ be a valid index into
--     'RayTracingPipelineCreateInfoKHR'::@pStages@ referring to a shader
--     of
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_RAYGEN_BIT_KHR',
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MISS_BIT_KHR',
--     or
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_CALLABLE_BIT_KHR'
--
-- -   If @type@ is 'RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR' then
--     @closestHitShader@, @anyHitShader@, and @intersectionShader@ /must/
--     be 'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR'
--
-- -   If @type@ is
--     'RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR' then
--     @intersectionShader@ /must/ be a valid index into
--     'RayTracingPipelineCreateInfoKHR'::@pStages@ referring to a shader
--     of
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_INTERSECTION_BIT_KHR'
--
-- -   If @type@ is 'RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR'
--     then @intersectionShader@ /must/ be
--     'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR'
--
-- -   @closestHitShader@ /must/ be either
--     'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR' or a valid index into
--     'RayTracingPipelineCreateInfoKHR'::@pStages@ referring to a shader
--     of
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_CLOSEST_HIT_BIT_KHR'
--
-- -   @anyHitShader@ /must/ be either
--     'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR' or a valid index into
--     'RayTracingPipelineCreateInfoKHR'::@pStages@ referring to a shader
--     of
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_ANY_HIT_BIT_KHR'
--
-- -   If
--     'PhysicalDeviceRayTracingFeaturesKHR'::@rayTracingShaderGroupHandleCaptureReplayMixed@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE' then
--     @pShaderGroupCaptureReplayHandle@ /must/ not be provided if it has
--     not been provided on a previous call to ray tracing pipeline
--     creation
--
-- -   If
--     'PhysicalDeviceRayTracingFeaturesKHR'::@rayTracingShaderGroupHandleCaptureReplayMixed@
--     is 'Vulkan.Core10.FundamentalTypes.FALSE' then the caller /must/
--     guarantee that no ray tracing pipeline creation commands with
--     @pShaderGroupCaptureReplayHandle@ provided execute simultaneously
--     with ray tracing pipeline creation commands without
--     @pShaderGroupCaptureReplayHandle@ provided
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_RAY_TRACING_SHADER_GROUP_CREATE_INFO_KHR'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @type@ /must/ be a valid 'RayTracingShaderGroupTypeKHR' value
--
-- = See Also
--
-- 'RayTracingPipelineCreateInfoKHR', 'RayTracingShaderGroupTypeKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data RayTracingShaderGroupCreateInfoKHR = RayTracingShaderGroupCreateInfoKHR
  { -- | @type@ is the type of hit group specified in this structure.
    RayTracingShaderGroupCreateInfoKHR -> RayTracingShaderGroupTypeKHR
type' :: RayTracingShaderGroupTypeKHR
  , -- | @generalShader@ is the index of the ray generation, miss, or callable
    -- shader from 'RayTracingPipelineCreateInfoKHR'::@pStages@ in the group if
    -- the shader group has @type@ of
    -- 'RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR', and
    -- 'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR' otherwise.
    RayTracingShaderGroupCreateInfoKHR -> "bindInfoCount" ::: Word32
generalShader :: Word32
  , -- | @closestHitShader@ is the optional index of the closest hit shader from
    -- 'RayTracingPipelineCreateInfoKHR'::@pStages@ in the group if the shader
    -- group has @type@ of
    -- 'RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR' or
    -- 'RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR', and
    -- 'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR' otherwise.
    RayTracingShaderGroupCreateInfoKHR -> "bindInfoCount" ::: Word32
closestHitShader :: Word32
  , -- | @anyHitShader@ is the optional index of the any-hit shader from
    -- 'RayTracingPipelineCreateInfoKHR'::@pStages@ in the group if the shader
    -- group has @type@ of
    -- 'RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR' or
    -- 'RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR', and
    -- 'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR' otherwise.
    RayTracingShaderGroupCreateInfoKHR -> "bindInfoCount" ::: Word32
anyHitShader :: Word32
  , -- | @intersectionShader@ is the index of the intersection shader from
    -- 'RayTracingPipelineCreateInfoKHR'::@pStages@ in the group if the shader
    -- group has @type@ of
    -- 'RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR', and
    -- 'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR' otherwise.
    RayTracingShaderGroupCreateInfoKHR -> "bindInfoCount" ::: Word32
intersectionShader :: Word32
  , -- | @pShaderGroupCaptureReplayHandle@ is an optional pointer to replay
    -- information for this shader group. Ignored if
    -- 'PhysicalDeviceRayTracingFeaturesKHR'::@rayTracingShaderGroupHandleCaptureReplay@
    -- is 'Vulkan.Core10.FundamentalTypes.FALSE'.
    RayTracingShaderGroupCreateInfoKHR -> "data" ::: Ptr ()
shaderGroupCaptureReplayHandle :: Ptr ()
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RayTracingShaderGroupCreateInfoKHR)
#endif
deriving instance Show RayTracingShaderGroupCreateInfoKHR

instance ToCStruct RayTracingShaderGroupCreateInfoKHR where
  withCStruct :: RayTracingShaderGroupCreateInfoKHR
-> (Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b
withCStruct x :: RayTracingShaderGroupCreateInfoKHR
x f :: Ptr RayTracingShaderGroupCreateInfoKHR -> IO b
f = Int
-> Int -> (Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b)
-> (Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr RayTracingShaderGroupCreateInfoKHR
p -> Ptr RayTracingShaderGroupCreateInfoKHR
-> RayTracingShaderGroupCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr RayTracingShaderGroupCreateInfoKHR
p RayTracingShaderGroupCreateInfoKHR
x (Ptr RayTracingShaderGroupCreateInfoKHR -> IO b
f Ptr RayTracingShaderGroupCreateInfoKHR
p)
  pokeCStruct :: Ptr RayTracingShaderGroupCreateInfoKHR
-> RayTracingShaderGroupCreateInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr RayTracingShaderGroupCreateInfoKHR
p RayTracingShaderGroupCreateInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RAY_TRACING_SHADER_GROUP_CREATE_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr RayTracingShaderGroupTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr RayTracingShaderGroupTypeKHR)) (RayTracingShaderGroupTypeKHR
type')
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("bindInfoCount" ::: Word32
generalShader)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("bindInfoCount" ::: Word32
closestHitShader)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) ("bindInfoCount" ::: Word32
anyHitShader)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ("bindInfoCount" ::: Word32
intersectionShader)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
shaderGroupCaptureReplayHandle)
    IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr RayTracingShaderGroupCreateInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr RayTracingShaderGroupCreateInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RAY_TRACING_SHADER_GROUP_CREATE_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr RayTracingShaderGroupTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr RayTracingShaderGroupTypeKHR)) (RayTracingShaderGroupTypeKHR
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct RayTracingShaderGroupCreateInfoKHR where
  peekCStruct :: Ptr RayTracingShaderGroupCreateInfoKHR
-> IO RayTracingShaderGroupCreateInfoKHR
peekCStruct p :: Ptr RayTracingShaderGroupCreateInfoKHR
p = do
    RayTracingShaderGroupTypeKHR
type' <- Ptr RayTracingShaderGroupTypeKHR -> IO RayTracingShaderGroupTypeKHR
forall a. Storable a => Ptr a -> IO a
peek @RayTracingShaderGroupTypeKHR ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr RayTracingShaderGroupTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr RayTracingShaderGroupTypeKHR))
    "bindInfoCount" ::: Word32
generalShader <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    "bindInfoCount" ::: Word32
closestHitShader <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    "bindInfoCount" ::: Word32
anyHitShader <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
    "bindInfoCount" ::: Word32
intersectionShader <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    "data" ::: Ptr ()
pShaderGroupCaptureReplayHandle <- Ptr ("data" ::: Ptr ()) -> IO ("data" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr RayTracingShaderGroupCreateInfoKHR
p Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr ())))
    RayTracingShaderGroupCreateInfoKHR
-> IO RayTracingShaderGroupCreateInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RayTracingShaderGroupCreateInfoKHR
 -> IO RayTracingShaderGroupCreateInfoKHR)
-> RayTracingShaderGroupCreateInfoKHR
-> IO RayTracingShaderGroupCreateInfoKHR
forall a b. (a -> b) -> a -> b
$ RayTracingShaderGroupTypeKHR
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("data" ::: Ptr ())
-> RayTracingShaderGroupCreateInfoKHR
RayTracingShaderGroupCreateInfoKHR
             RayTracingShaderGroupTypeKHR
type' "bindInfoCount" ::: Word32
generalShader "bindInfoCount" ::: Word32
closestHitShader "bindInfoCount" ::: Word32
anyHitShader "bindInfoCount" ::: Word32
intersectionShader "data" ::: Ptr ()
pShaderGroupCaptureReplayHandle

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

instance Zero RayTracingShaderGroupCreateInfoKHR where
  zero :: RayTracingShaderGroupCreateInfoKHR
zero = RayTracingShaderGroupTypeKHR
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("data" ::: Ptr ())
-> RayTracingShaderGroupCreateInfoKHR
RayTracingShaderGroupCreateInfoKHR
           RayTracingShaderGroupTypeKHR
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "data" ::: Ptr ()
forall a. Zero a => a
zero


-- | VkRayTracingPipelineCreateInfoKHR - Structure specifying parameters of a
-- newly created ray tracing pipeline
--
-- = Description
--
-- The parameters @basePipelineHandle@ and @basePipelineIndex@ are
-- described in more detail in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipelines-pipeline-derivatives Pipeline Derivatives>.
--
-- When
-- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_LIBRARY_BIT_KHR'
-- is specified, this pipeline defines a /pipeline library/ which /cannot/
-- be bound as a ray tracing pipeline directly. Instead, pipeline libraries
-- define common shaders and shader groups which /can/ be included in
-- future pipeline creation.
--
-- If pipeline libraries are included in @libraries@, shaders defined in
-- those libraries are treated as if they were defined as additional
-- entries in @pStages@, appended in the order they appear in the
-- @pLibraries@ array and in the @pStages@ array when those libraries were
-- defined.
--
-- When referencing shader groups in order to obtain a shader group handle,
-- groups defined in those libraries are treated as if they were defined as
-- additional entries in @pGroups@, appended in the order they appear in
-- the @pLibraries@ array and in the @pGroups@ array when those libraries
-- were defined. The shaders these groups reference are set when the
-- pipeline library is created, referencing those specified in the pipeline
-- library, not in the pipeline that includes it.
--
-- If the
-- 'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
-- structure is included in the @pNext@ chain of
-- 'RayTracingPipelineCreateInfoKHR', the operation of this pipeline
-- creation is /deferred/, as defined in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#deferred-host-operations Deferred Host Operations>
-- chapter.
--
-- == Valid Usage
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineIndex@ is @-1@, @basePipelineHandle@ /must/
--     be a valid handle to a ray tracing 'Vulkan.Core10.Handles.Pipeline'
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineHandle@ is
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @basePipelineIndex@ /must/
--     be a valid index into the calling command’s @pCreateInfos@ parameter
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineIndex@ is not @-1@, @basePipelineHandle@
--     /must/ be 'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If @flags@ contains the
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_DERIVATIVE_BIT'
--     flag, and @basePipelineHandle@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @basePipelineIndex@ /must/
--     be @-1@
--
-- -   The @stage@ member of at least one element of @pStages@ /must/ be
--     'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_RAYGEN_BIT_KHR'
--
-- -   The shader code for the entry points identified by @pStages@, and
--     the rest of the state identified by this structure /must/ adhere to
--     the pipeline linking rules described in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces Shader Interfaces>
--     chapter
--
-- -   @layout@ /must/ be
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-pipelinelayout-consistency consistent>
--     with all shaders specified in @pStages@
--
-- -   The number of resources in @layout@ accessible to each shader stage
--     that is used by the pipeline /must/ be less than or equal to
--     'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxPerStageResources@
--
-- -   @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_INDIRECT_BINDABLE_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineCreationCacheControl pipelineCreationCacheControl>
--     feature is not enabled, @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_FAIL_ON_PIPELINE_COMPILE_REQUIRED_BIT_EXT'
--     or
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_EARLY_RETURN_ON_FAILURE_BIT_EXT'
--
-- -   @maxRecursionDepth@ /must/ be less than or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxRecursionDepth@
--
-- -   If @flags@ includes
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_LIBRARY_BIT_KHR',
--     @pLibraryInterface@ /must/ not be @NULL@
--
-- -   If the @libraryCount@ member of @libraries@ is greater than @0@,
--     @pLibraryInterface@ /must/ not be @NULL@
--
-- -   Each element of the @pLibraries@ member of @libraries@ /must/ have
--     been created with the value of @maxRecursionDepth@ equal to that in
--     this pipeline
--
-- -   Each element of the @pLibraries@ member of @libraries@ /must/ have
--     been created with a @layout@ that is compatible with the @layout@ in
--     this pipeline
--
-- -   Each element of the @pLibraries@ member of @libraries@ /must/ have
--     been created with values of the @maxPayloadSize@,
--     @maxAttributeSize@, and @maxCallableSize@ members of
--     @pLibraryInterface@ equal to those in this pipeline
--
-- -   If @flags@ includes
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_ANY_HIT_SHADERS_BIT_KHR',
--     for any element of @pGroups@ with a @type@ of
--     'RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR' or
--     'RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR', the
--     @anyHitShader@ of that element /must/ not be
--     'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR'
--
-- -   If @flags@ includes
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_NO_NULL_CLOSEST_HIT_SHADERS_BIT_KHR',
--     for any element of @pGroups@ with a @type@ of
--     'RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR' or
--     'RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR', the
--     @closestHitShader@ of that element /must/ not be
--     'Vulkan.Core10.APIConstants.SHADER_UNUSED_KHR'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPrimitiveCulling rayTracingPrimitiveCulling>
--     feature is not enabled, @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_SKIP_AABBS_BIT_KHR'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-rayTracingPrimitiveCulling rayTracingPrimitiveCulling>
--     feature is not enabled, @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PIPELINE_CREATE_RAY_TRACING_SKIP_TRIANGLES_BIT_KHR'
--
-- -   If @libraries.libraryCount@ is zero, then @stageCount@ /must/ not be
--     zero
--
-- -   If @libraries.libraryCount@ is zero, then @groupCount@ /must/ not be
--     zero
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_RAY_TRACING_PIPELINE_CREATE_INFO_KHR'
--
-- -   Each @pNext@ member of any structure (including this one) in the
--     @pNext@ chain /must/ be either @NULL@ or a pointer to a valid
--     instance of
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--     or
--     'Vulkan.Extensions.VK_EXT_pipeline_creation_feedback.PipelineCreationFeedbackCreateInfoEXT'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @flags@ /must/ be a valid combination of
--     'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlagBits'
--     values
--
-- -   If @stageCount@ is not @0@, @pStages@ /must/ be a valid pointer to
--     an array of @stageCount@ valid
--     'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo' structures
--
-- -   If @groupCount@ is not @0@, @pGroups@ /must/ be a valid pointer to
--     an array of @groupCount@ valid 'RayTracingShaderGroupCreateInfoKHR'
--     structures
--
-- -   @libraries@ /must/ be a valid
--     'Vulkan.Extensions.VK_KHR_pipeline_library.PipelineLibraryCreateInfoKHR'
--     structure
--
-- -   If @pLibraryInterface@ is not @NULL@, @pLibraryInterface@ /must/ be
--     a valid pointer to a valid
--     'RayTracingPipelineInterfaceCreateInfoKHR' structure
--
-- -   @layout@ /must/ be a valid 'Vulkan.Core10.Handles.PipelineLayout'
--     handle
--
-- -   Both of @basePipelineHandle@, and @layout@ that are valid handles of
--     non-ignored parameters /must/ have been created, allocated, or
--     retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Pipeline',
-- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlags',
-- 'Vulkan.Core10.Handles.PipelineLayout',
-- 'Vulkan.Extensions.VK_KHR_pipeline_library.PipelineLibraryCreateInfoKHR',
-- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo',
-- 'RayTracingPipelineInterfaceCreateInfoKHR',
-- 'RayTracingShaderGroupCreateInfoKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'createRayTracingPipelinesKHR'
data RayTracingPipelineCreateInfoKHR (es :: [Type]) = RayTracingPipelineCreateInfoKHR
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    RayTracingPipelineCreateInfoKHR es -> Chain es
next :: Chain es
  , -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.PipelineCreateFlagBits.PipelineCreateFlagBits'
    -- specifying how the pipeline will be generated.
    RayTracingPipelineCreateInfoKHR es -> PipelineCreateFlags
flags :: PipelineCreateFlags
  , -- | @pStages@ is a pointer to an array of @stageCount@
    -- 'Vulkan.Core10.Pipeline.PipelineShaderStageCreateInfo' structures
    -- describing the set of the shader stages to be included in the ray
    -- tracing pipeline.
    RayTracingPipelineCreateInfoKHR es
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
stages :: Vector (SomeStruct PipelineShaderStageCreateInfo)
  , -- | @pGroups@ is a pointer to an array of @groupCount@
    -- 'RayTracingShaderGroupCreateInfoKHR' structures describing the set of
    -- the shader stages to be included in each shader group in the ray tracing
    -- pipeline.
    RayTracingPipelineCreateInfoKHR es
-> Vector RayTracingShaderGroupCreateInfoKHR
groups :: Vector RayTracingShaderGroupCreateInfoKHR
  , -- | @maxRecursionDepth@ is the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#ray-tracing-recursion-depth maximum recursion depth>
    -- of shaders executed by this pipeline.
    RayTracingPipelineCreateInfoKHR es -> "bindInfoCount" ::: Word32
maxRecursionDepth :: Word32
  , -- | @libraries@ is a
    -- 'Vulkan.Extensions.VK_KHR_pipeline_library.PipelineLibraryCreateInfoKHR'
    -- structure defining pipeline libraries to include.
    RayTracingPipelineCreateInfoKHR es -> PipelineLibraryCreateInfoKHR
libraries :: PipelineLibraryCreateInfoKHR
  , -- | @pLibraryInterface@ is a pointer to a
    -- 'RayTracingPipelineInterfaceCreateInfoKHR' structure defining additional
    -- information when using pipeline libraries.
    RayTracingPipelineCreateInfoKHR es
-> Maybe RayTracingPipelineInterfaceCreateInfoKHR
libraryInterface :: Maybe RayTracingPipelineInterfaceCreateInfoKHR
  , -- | @layout@ is the description of binding locations used by both the
    -- pipeline and descriptor sets used with the pipeline.
    RayTracingPipelineCreateInfoKHR es -> PipelineLayout
layout :: PipelineLayout
  , -- | @basePipelineHandle@ is a pipeline to derive from.
    RayTracingPipelineCreateInfoKHR es -> Pipeline
basePipelineHandle :: Pipeline
  , -- | @basePipelineIndex@ is an index into the @pCreateInfos@ parameter to use
    -- as a pipeline to derive from.
    RayTracingPipelineCreateInfoKHR es -> Int32
basePipelineIndex :: Int32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RayTracingPipelineCreateInfoKHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (RayTracingPipelineCreateInfoKHR es)

instance Extensible RayTracingPipelineCreateInfoKHR where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_RAY_TRACING_PIPELINE_CREATE_INFO_KHR
  setNext :: RayTracingPipelineCreateInfoKHR ds
-> Chain es -> RayTracingPipelineCreateInfoKHR es
setNext x :: RayTracingPipelineCreateInfoKHR ds
x next :: Chain es
next = RayTracingPipelineCreateInfoKHR ds
x{$sel:next:RayTracingPipelineCreateInfoKHR :: Chain es
next = Chain es
next}
  getNext :: RayTracingPipelineCreateInfoKHR es -> Chain es
getNext RayTracingPipelineCreateInfoKHR{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends RayTracingPipelineCreateInfoKHR e => b) -> Maybe b
  extends :: proxy e
-> (Extends RayTracingPipelineCreateInfoKHR e => b) -> Maybe b
extends _ f :: Extends RayTracingPipelineCreateInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable DeferredOperationInfoKHR) =>
Maybe (e :~: DeferredOperationInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeferredOperationInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends RayTracingPipelineCreateInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable PipelineCreationFeedbackCreateInfoEXT) =>
Maybe (e :~: PipelineCreationFeedbackCreateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PipelineCreationFeedbackCreateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends RayTracingPipelineCreateInfoKHR e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss RayTracingPipelineCreateInfoKHR es, PokeChain es) => ToCStruct (RayTracingPipelineCreateInfoKHR es) where
  withCStruct :: RayTracingPipelineCreateInfoKHR es
-> (Ptr (RayTracingPipelineCreateInfoKHR es) -> IO b) -> IO b
withCStruct x :: RayTracingPipelineCreateInfoKHR es
x f :: Ptr (RayTracingPipelineCreateInfoKHR es) -> IO b
f = Int
-> Int
-> (Ptr (RayTracingPipelineCreateInfoKHR es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 120 8 ((Ptr (RayTracingPipelineCreateInfoKHR es) -> IO b) -> IO b)
-> (Ptr (RayTracingPipelineCreateInfoKHR es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (RayTracingPipelineCreateInfoKHR es)
p -> Ptr (RayTracingPipelineCreateInfoKHR es)
-> RayTracingPipelineCreateInfoKHR es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (RayTracingPipelineCreateInfoKHR es)
p RayTracingPipelineCreateInfoKHR es
x (Ptr (RayTracingPipelineCreateInfoKHR es) -> IO b
f Ptr (RayTracingPipelineCreateInfoKHR es)
p)
  pokeCStruct :: Ptr (RayTracingPipelineCreateInfoKHR es)
-> RayTracingPipelineCreateInfoKHR es -> IO b -> IO b
pokeCStruct p :: Ptr (RayTracingPipelineCreateInfoKHR es)
p RayTracingPipelineCreateInfoKHR{..} f :: 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 (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RAY_TRACING_PIPELINE_CREATE_INFO_KHR)
    "data" ::: Ptr ()
pNext'' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    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 (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext''
    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 PipelineCreateFlags -> PipelineCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr PipelineCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineCreateFlags)) (PipelineCreateFlags
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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector (SomeStruct PipelineShaderStageCreateInfo) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct PipelineShaderStageCreateInfo) -> Int)
-> Vector (SomeStruct PipelineShaderStageCreateInfo) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (SomeStruct PipelineShaderStageCreateInfo)
stages)) :: Word32))
    Ptr (PipelineShaderStageCreateInfo Any)
pPStages' <- ((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any)))
-> ((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(PipelineShaderStageCreateInfo _) ((Vector (SomeStruct PipelineShaderStageCreateInfo) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (SomeStruct PipelineShaderStageCreateInfo)
stages)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) 8
    (Int -> SomeStruct PipelineShaderStageCreateInfo -> ContT b IO ())
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct PipelineShaderStageCreateInfo
e -> ((() -> 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 (SomeStruct PipelineShaderStageCreateInfo)
-> SomeStruct PipelineShaderStageCreateInfo -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (PipelineShaderStageCreateInfo Any)
-> Ptr (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineShaderStageCreateInfo Any)
pPStages' Ptr (PipelineShaderStageCreateInfo Any)
-> Int -> Ptr (PipelineShaderStageCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (PipelineShaderStageCreateInfo _))) (SomeStruct PipelineShaderStageCreateInfo
e) (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
$ ())) (Vector (SomeStruct PipelineShaderStageCreateInfo)
stages)
    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 (PipelineShaderStageCreateInfo Any))
-> Ptr (PipelineShaderStageCreateInfo Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr (Ptr (PipelineShaderStageCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (PipelineShaderStageCreateInfo _)))) (Ptr (PipelineShaderStageCreateInfo Any)
pPStages')
    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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector RayTracingShaderGroupCreateInfoKHR -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector RayTracingShaderGroupCreateInfoKHR -> Int)
-> Vector RayTracingShaderGroupCreateInfoKHR -> Int
forall a b. (a -> b) -> a -> b
$ (Vector RayTracingShaderGroupCreateInfoKHR
groups)) :: Word32))
    Ptr RayTracingShaderGroupCreateInfoKHR
pPGroups' <- ((Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b)
-> ContT b IO (Ptr RayTracingShaderGroupCreateInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b)
 -> ContT b IO (Ptr RayTracingShaderGroupCreateInfoKHR))
-> ((Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b)
-> ContT b IO (Ptr RayTracingShaderGroupCreateInfoKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @RayTracingShaderGroupCreateInfoKHR ((Vector RayTracingShaderGroupCreateInfoKHR -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector RayTracingShaderGroupCreateInfoKHR
groups)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) 8
    (Int -> RayTracingShaderGroupCreateInfoKHR -> ContT b IO ())
-> Vector RayTracingShaderGroupCreateInfoKHR -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: RayTracingShaderGroupCreateInfoKHR
e -> ((() -> 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 RayTracingShaderGroupCreateInfoKHR
-> RayTracingShaderGroupCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr RayTracingShaderGroupCreateInfoKHR
pPGroups' Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr RayTracingShaderGroupCreateInfoKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr RayTracingShaderGroupCreateInfoKHR) (RayTracingShaderGroupCreateInfoKHR
e) (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
$ ())) (Vector RayTracingShaderGroupCreateInfoKHR
groups)
    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 RayTracingShaderGroupCreateInfoKHR)
-> Ptr RayTracingShaderGroupCreateInfoKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr (Ptr RayTracingShaderGroupCreateInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr RayTracingShaderGroupCreateInfoKHR))) (Ptr RayTracingShaderGroupCreateInfoKHR
pPGroups')
    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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ("bindInfoCount" ::: Word32
maxRecursionDepth)
    ((() -> 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 PipelineLibraryCreateInfoKHR
-> PipelineLibraryCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr PipelineLibraryCreateInfoKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr PipelineLibraryCreateInfoKHR)) (PipelineLibraryCreateInfoKHR
libraries) (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
$ ())
    Ptr RayTracingPipelineInterfaceCreateInfoKHR
pLibraryInterface'' <- case (Maybe RayTracingPipelineInterfaceCreateInfoKHR
libraryInterface) of
      Nothing -> Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> ContT b IO (Ptr RayTracingPipelineInterfaceCreateInfoKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr RayTracingPipelineInterfaceCreateInfoKHR
forall a. Ptr a
nullPtr
      Just j :: RayTracingPipelineInterfaceCreateInfoKHR
j -> ((Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b) -> IO b)
-> ContT b IO (Ptr RayTracingPipelineInterfaceCreateInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b) -> IO b)
 -> ContT b IO (Ptr RayTracingPipelineInterfaceCreateInfoKHR))
-> ((Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b) -> IO b)
-> ContT b IO (Ptr RayTracingPipelineInterfaceCreateInfoKHR)
forall a b. (a -> b) -> a -> b
$ RayTracingPipelineInterfaceCreateInfoKHR
-> (Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (RayTracingPipelineInterfaceCreateInfoKHR
j)
    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 RayTracingPipelineInterfaceCreateInfoKHR)
-> Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr (Ptr RayTracingPipelineInterfaceCreateInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr (Ptr RayTracingPipelineInterfaceCreateInfoKHR))) Ptr RayTracingPipelineInterfaceCreateInfoKHR
pLibraryInterface''
    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 PipelineLayout -> PipelineLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr PipelineLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr PipelineLayout)) (PipelineLayout
layout)
    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
$ ("pPipelines" ::: Ptr Pipeline) -> Pipeline -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> "pPipelines" ::: Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Pipeline)) (Pipeline
basePipelineHandle)
    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 Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es) -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Int32)) (Int32
basePipelineIndex)
    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 = 120
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (RayTracingPipelineCreateInfoKHR es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (RayTracingPipelineCreateInfoKHR es)
p f :: 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 (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RAY_TRACING_PIPELINE_CREATE_INFO_KHR)
    "data" ::: Ptr ()
pNext' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    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 (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext'
    Ptr (PipelineShaderStageCreateInfo Any)
pPStages' <- ((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
 -> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any)))
-> ((Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b)
-> ContT b IO (Ptr (PipelineShaderStageCreateInfo Any))
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (Ptr (PipelineShaderStageCreateInfo Any) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(PipelineShaderStageCreateInfo _) ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) 8
    (Int -> SomeStruct PipelineShaderStageCreateInfo -> ContT b IO ())
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct PipelineShaderStageCreateInfo
e -> ((() -> 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 (SomeStruct PipelineShaderStageCreateInfo)
-> SomeStruct PipelineShaderStageCreateInfo -> IO b -> IO b
forall (a :: [*] -> *) b.
(forall (es :: [*]).
 (Extendss a es, PokeChain es) =>
 ToCStruct (a es)) =>
Ptr (SomeStruct a) -> SomeStruct a -> IO b -> IO b
pokeSomeCStruct (Ptr (PipelineShaderStageCreateInfo Any)
-> Ptr (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (PipelineShaderStageCreateInfo Any)
pPStages' Ptr (PipelineShaderStageCreateInfo Any)
-> Int -> Ptr (PipelineShaderStageCreateInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (PipelineShaderStageCreateInfo _))) (SomeStruct PipelineShaderStageCreateInfo
e) (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
$ ())) (Vector (SomeStruct PipelineShaderStageCreateInfo)
forall a. Monoid a => a
mempty)
    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 (PipelineShaderStageCreateInfo Any))
-> Ptr (PipelineShaderStageCreateInfo Any) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr (Ptr (PipelineShaderStageCreateInfo _))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (PipelineShaderStageCreateInfo _)))) (Ptr (PipelineShaderStageCreateInfo Any)
pPStages')
    Ptr RayTracingShaderGroupCreateInfoKHR
pPGroups' <- ((Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b)
-> ContT b IO (Ptr RayTracingShaderGroupCreateInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b)
 -> ContT b IO (Ptr RayTracingShaderGroupCreateInfoKHR))
-> ((Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b)
-> ContT b IO (Ptr RayTracingShaderGroupCreateInfoKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (Ptr RayTracingShaderGroupCreateInfoKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @RayTracingShaderGroupCreateInfoKHR ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) 8
    (Int -> RayTracingShaderGroupCreateInfoKHR -> ContT b IO ())
-> Vector RayTracingShaderGroupCreateInfoKHR -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: RayTracingShaderGroupCreateInfoKHR
e -> ((() -> 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 RayTracingShaderGroupCreateInfoKHR
-> RayTracingShaderGroupCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr RayTracingShaderGroupCreateInfoKHR
pPGroups' Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr RayTracingShaderGroupCreateInfoKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr RayTracingShaderGroupCreateInfoKHR) (RayTracingShaderGroupCreateInfoKHR
e) (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
$ ())) (Vector RayTracingShaderGroupCreateInfoKHR
forall a. Monoid a => a
mempty)
    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 RayTracingShaderGroupCreateInfoKHR)
-> Ptr RayTracingShaderGroupCreateInfoKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr (Ptr RayTracingShaderGroupCreateInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr RayTracingShaderGroupCreateInfoKHR))) (Ptr RayTracingShaderGroupCreateInfoKHR
pPGroups')
    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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ("bindInfoCount" ::: Word32
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 PipelineLibraryCreateInfoKHR
-> PipelineLibraryCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr PipelineLibraryCreateInfoKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr PipelineLibraryCreateInfoKHR)) (PipelineLibraryCreateInfoKHR
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 PipelineLayout -> PipelineLayout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr PipelineLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr PipelineLayout)) (PipelineLayout
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 Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es) -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Int32)) (Int32
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 (Extendss RayTracingPipelineCreateInfoKHR es, PeekChain es) => FromCStruct (RayTracingPipelineCreateInfoKHR es) where
  peekCStruct :: Ptr (RayTracingPipelineCreateInfoKHR es)
-> IO (RayTracingPipelineCreateInfoKHR es)
peekCStruct p :: Ptr (RayTracingPipelineCreateInfoKHR es)
p = do
    "data" ::: Ptr ()
pNext <- Ptr ("data" ::: Ptr ()) -> IO ("data" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (("data" ::: Ptr ()) -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr "data" ::: Ptr ()
pNext)
    PipelineCreateFlags
flags <- Ptr PipelineCreateFlags -> IO PipelineCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineCreateFlags ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr PipelineCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PipelineCreateFlags))
    "bindInfoCount" ::: Word32
stageCount <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    Ptr (PipelineShaderStageCreateInfo Any)
pStages <- Ptr (Ptr (PipelineShaderStageCreateInfo Any))
-> IO (Ptr (PipelineShaderStageCreateInfo Any))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (PipelineShaderStageCreateInfo _)) ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr (Ptr (PipelineShaderStageCreateInfo a))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr (PipelineShaderStageCreateInfo a))))
    Vector (SomeStruct PipelineShaderStageCreateInfo)
pStages' <- Int
-> (Int -> IO (SomeStruct PipelineShaderStageCreateInfo))
-> IO (Vector (SomeStruct PipelineShaderStageCreateInfo))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("bindInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "bindInfoCount" ::: Word32
stageCount) (\i :: Int
i -> Ptr (SomeStruct PipelineShaderStageCreateInfo)
-> IO (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *).
(Extensible a,
 forall (es :: [*]).
 (Extendss a es, PeekChain es) =>
 FromCStruct (a es)) =>
Ptr (SomeStruct a) -> IO (SomeStruct a)
peekSomeCStruct (Ptr (PipelineShaderStageCreateInfo Any)
-> Ptr (SomeStruct PipelineShaderStageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions ((Ptr (PipelineShaderStageCreateInfo Any)
pStages Ptr (PipelineShaderStageCreateInfo Any)
-> Int -> Ptr (PipelineShaderStageCreateInfo Any)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (PipelineShaderStageCreateInfo _)))))
    "bindInfoCount" ::: Word32
groupCount <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr RayTracingShaderGroupCreateInfoKHR
pGroups <- Ptr (Ptr RayTracingShaderGroupCreateInfoKHR)
-> IO (Ptr RayTracingShaderGroupCreateInfoKHR)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr RayTracingShaderGroupCreateInfoKHR) ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr (Ptr RayTracingShaderGroupCreateInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr RayTracingShaderGroupCreateInfoKHR)))
    Vector RayTracingShaderGroupCreateInfoKHR
pGroups' <- Int
-> (Int -> IO RayTracingShaderGroupCreateInfoKHR)
-> IO (Vector RayTracingShaderGroupCreateInfoKHR)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("bindInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "bindInfoCount" ::: Word32
groupCount) (\i :: Int
i -> Ptr RayTracingShaderGroupCreateInfoKHR
-> IO RayTracingShaderGroupCreateInfoKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @RayTracingShaderGroupCreateInfoKHR ((Ptr RayTracingShaderGroupCreateInfoKHR
pGroups Ptr RayTracingShaderGroupCreateInfoKHR
-> Int -> Ptr RayTracingShaderGroupCreateInfoKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr RayTracingShaderGroupCreateInfoKHR)))
    "bindInfoCount" ::: Word32
maxRecursionDepth <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    PipelineLibraryCreateInfoKHR
libraries <- Ptr PipelineLibraryCreateInfoKHR -> IO PipelineLibraryCreateInfoKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PipelineLibraryCreateInfoKHR ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr PipelineLibraryCreateInfoKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr PipelineLibraryCreateInfoKHR))
    Ptr RayTracingPipelineInterfaceCreateInfoKHR
pLibraryInterface <- Ptr (Ptr RayTracingPipelineInterfaceCreateInfoKHR)
-> IO (Ptr RayTracingPipelineInterfaceCreateInfoKHR)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr RayTracingPipelineInterfaceCreateInfoKHR) ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr (Ptr RayTracingPipelineInterfaceCreateInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr (Ptr RayTracingPipelineInterfaceCreateInfoKHR)))
    Maybe RayTracingPipelineInterfaceCreateInfoKHR
pLibraryInterface' <- (Ptr RayTracingPipelineInterfaceCreateInfoKHR
 -> IO RayTracingPipelineInterfaceCreateInfoKHR)
-> Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> IO (Maybe RayTracingPipelineInterfaceCreateInfoKHR)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr RayTracingPipelineInterfaceCreateInfoKHR
j -> Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> IO RayTracingPipelineInterfaceCreateInfoKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @RayTracingPipelineInterfaceCreateInfoKHR (Ptr RayTracingPipelineInterfaceCreateInfoKHR
j)) Ptr RayTracingPipelineInterfaceCreateInfoKHR
pLibraryInterface
    PipelineLayout
layout <- Ptr PipelineLayout -> IO PipelineLayout
forall a. Storable a => Ptr a -> IO a
peek @PipelineLayout ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> Ptr PipelineLayout
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr PipelineLayout))
    Pipeline
basePipelineHandle <- ("pPipelines" ::: Ptr Pipeline) -> IO Pipeline
forall a. Storable a => Ptr a -> IO a
peek @Pipeline ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es)
-> Int -> "pPipelines" ::: Ptr Pipeline
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr Pipeline))
    Int32
basePipelineIndex <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek @Int32 ((Ptr (RayTracingPipelineCreateInfoKHR es)
p Ptr (RayTracingPipelineCreateInfoKHR es) -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr Int32))
    RayTracingPipelineCreateInfoKHR es
-> IO (RayTracingPipelineCreateInfoKHR es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RayTracingPipelineCreateInfoKHR es
 -> IO (RayTracingPipelineCreateInfoKHR es))
-> RayTracingPipelineCreateInfoKHR es
-> IO (RayTracingPipelineCreateInfoKHR es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> PipelineCreateFlags
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> Vector RayTracingShaderGroupCreateInfoKHR
-> ("bindInfoCount" ::: Word32)
-> PipelineLibraryCreateInfoKHR
-> Maybe RayTracingPipelineInterfaceCreateInfoKHR
-> PipelineLayout
-> Pipeline
-> Int32
-> RayTracingPipelineCreateInfoKHR es
forall (es :: [*]).
Chain es
-> PipelineCreateFlags
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> Vector RayTracingShaderGroupCreateInfoKHR
-> ("bindInfoCount" ::: Word32)
-> PipelineLibraryCreateInfoKHR
-> Maybe RayTracingPipelineInterfaceCreateInfoKHR
-> PipelineLayout
-> Pipeline
-> Int32
-> RayTracingPipelineCreateInfoKHR es
RayTracingPipelineCreateInfoKHR
             Chain es
next PipelineCreateFlags
flags Vector (SomeStruct PipelineShaderStageCreateInfo)
pStages' Vector RayTracingShaderGroupCreateInfoKHR
pGroups' "bindInfoCount" ::: Word32
maxRecursionDepth PipelineLibraryCreateInfoKHR
libraries Maybe RayTracingPipelineInterfaceCreateInfoKHR
pLibraryInterface' PipelineLayout
layout Pipeline
basePipelineHandle Int32
basePipelineIndex

instance es ~ '[] => Zero (RayTracingPipelineCreateInfoKHR es) where
  zero :: RayTracingPipelineCreateInfoKHR es
zero = Chain es
-> PipelineCreateFlags
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> Vector RayTracingShaderGroupCreateInfoKHR
-> ("bindInfoCount" ::: Word32)
-> PipelineLibraryCreateInfoKHR
-> Maybe RayTracingPipelineInterfaceCreateInfoKHR
-> PipelineLayout
-> Pipeline
-> Int32
-> RayTracingPipelineCreateInfoKHR es
forall (es :: [*]).
Chain es
-> PipelineCreateFlags
-> Vector (SomeStruct PipelineShaderStageCreateInfo)
-> Vector RayTracingShaderGroupCreateInfoKHR
-> ("bindInfoCount" ::: Word32)
-> PipelineLibraryCreateInfoKHR
-> Maybe RayTracingPipelineInterfaceCreateInfoKHR
-> PipelineLayout
-> Pipeline
-> Int32
-> RayTracingPipelineCreateInfoKHR es
RayTracingPipelineCreateInfoKHR
           ()
           PipelineCreateFlags
forall a. Zero a => a
zero
           Vector (SomeStruct PipelineShaderStageCreateInfo)
forall a. Monoid a => a
mempty
           Vector RayTracingShaderGroupCreateInfoKHR
forall a. Monoid a => a
mempty
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           PipelineLibraryCreateInfoKHR
forall a. Zero a => a
zero
           Maybe RayTracingPipelineInterfaceCreateInfoKHR
forall a. Maybe a
Nothing
           PipelineLayout
forall a. Zero a => a
zero
           Pipeline
forall a. Zero a => a
zero
           Int32
forall a. Zero a => a
zero


-- | VkBindAccelerationStructureMemoryInfoKHR - Structure specifying
-- acceleration structure memory binding
--
-- == Valid Usage
--
-- -   @accelerationStructure@ /must/ not already be backed by a memory
--     object
--
-- -   @memoryOffset@ /must/ be less than the size of @memory@
--
-- -   @memory@ /must/ have been allocated using one of the memory types
--     allowed in the @memoryTypeBits@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'getAccelerationStructureMemoryRequirementsKHR' with
--     @accelerationStructure@ and @type@ of
--     'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR'
--
-- -   @memoryOffset@ /must/ be an integer multiple of the @alignment@
--     member of the 'Vulkan.Core10.MemoryManagement.MemoryRequirements'
--     structure returned from a call to
--     'getAccelerationStructureMemoryRequirementsKHR' with
--     @accelerationStructure@ and @type@ of
--     'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR'
--
-- -   The @size@ member of the
--     'Vulkan.Core10.MemoryManagement.MemoryRequirements' structure
--     returned from a call to
--     'getAccelerationStructureMemoryRequirementsKHR' with
--     @accelerationStructure@ and @type@ of
--     'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR' /must/
--     be less than or equal to the size of @memory@ minus @memoryOffset@
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_BIND_ACCELERATION_STRUCTURE_MEMORY_INFO_KHR'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @accelerationStructure@ /must/ be a valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
--
-- -   @memory@ /must/ be a valid 'Vulkan.Core10.Handles.DeviceMemory'
--     handle
--
-- -   If @deviceIndexCount@ is not @0@, @pDeviceIndices@ /must/ be a valid
--     pointer to an array of @deviceIndexCount@ @uint32_t@ values
--
-- -   Both of @accelerationStructure@, and @memory@ /must/ have been
--     created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'Vulkan.Core10.Handles.DeviceMemory',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'bindAccelerationStructureMemoryKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.bindAccelerationStructureMemoryNV'
data BindAccelerationStructureMemoryInfoKHR = BindAccelerationStructureMemoryInfoKHR
  { -- | @accelerationStructure@ is the acceleration structure to be attached to
    -- memory.
    BindAccelerationStructureMemoryInfoKHR -> AccelerationStructureKHR
accelerationStructure :: AccelerationStructureKHR
  , -- | @memory@ is a 'Vulkan.Core10.Handles.DeviceMemory' object describing the
    -- device memory to attach.
    BindAccelerationStructureMemoryInfoKHR -> DeviceMemory
memory :: DeviceMemory
  , -- | @memoryOffset@ is the start offset of the region of memory that is to be
    -- bound to the acceleration structure. The number of bytes returned in the
    -- 'Vulkan.Core10.MemoryManagement.MemoryRequirements'::@size@ member in
    -- @memory@, starting from @memoryOffset@ bytes, will be bound to the
    -- specified acceleration structure.
    BindAccelerationStructureMemoryInfoKHR -> "dataSize" ::: Word64
memoryOffset :: DeviceSize
  , -- | @pDeviceIndices@ is a pointer to an array of device indices.
    BindAccelerationStructureMemoryInfoKHR
-> Vector ("bindInfoCount" ::: Word32)
deviceIndices :: Vector Word32
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (BindAccelerationStructureMemoryInfoKHR)
#endif
deriving instance Show BindAccelerationStructureMemoryInfoKHR

instance ToCStruct BindAccelerationStructureMemoryInfoKHR where
  withCStruct :: BindAccelerationStructureMemoryInfoKHR
-> (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
    -> IO b)
-> IO b
withCStruct x :: BindAccelerationStructureMemoryInfoKHR
x f :: ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> IO b
f = Int
-> Int
-> (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
  -> IO b)
 -> IO b)
-> (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p -> ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> BindAccelerationStructureMemoryInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p BindAccelerationStructureMemoryInfoKHR
x (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> IO b
f "pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p)
  pokeCStruct :: ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> BindAccelerationStructureMemoryInfoKHR -> IO b -> IO b
pokeCStruct p :: "pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p BindAccelerationStructureMemoryInfoKHR{..} f :: 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 (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_ACCELERATION_STRUCTURE_MEMORY_INFO_KHR)
    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 (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
accelerationStructure)
    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 DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceMemory)) (DeviceMemory
memory)
    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 (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) ("dataSize" ::: Word64
memoryOffset)
    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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector ("bindInfoCount" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("bindInfoCount" ::: Word32) -> Int)
-> Vector ("bindInfoCount" ::: Word32) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector ("bindInfoCount" ::: Word32)
deviceIndices)) :: Word32))
    Ptr ("bindInfoCount" ::: Word32)
pPDeviceIndices' <- ((Ptr ("bindInfoCount" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("bindInfoCount" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("bindInfoCount" ::: Word32) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("bindInfoCount" ::: Word32)))
-> ((Ptr ("bindInfoCount" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("bindInfoCount" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("bindInfoCount" ::: Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector ("bindInfoCount" ::: Word32) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector ("bindInfoCount" ::: Word32)
deviceIndices)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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 -> ("bindInfoCount" ::: Word32) -> IO ())
-> Vector ("bindInfoCount" ::: Word32) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "bindInfoCount" ::: Word32
e -> Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("bindInfoCount" ::: Word32)
pPDeviceIndices' Ptr ("bindInfoCount" ::: Word32)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) ("bindInfoCount" ::: Word32
e)) (Vector ("bindInfoCount" ::: Word32)
deviceIndices)
    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 ("bindInfoCount" ::: Word32))
-> Ptr ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr (Ptr ("bindInfoCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr Word32))) (Ptr ("bindInfoCount" ::: Word32)
pPDeviceIndices')
    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 = 56
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> IO b -> IO b
pokeZeroCStruct p :: "pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p f :: 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 (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_BIND_ACCELERATION_STRUCTURE_MEMORY_INFO_KHR)
    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 (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
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 DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceMemory)) (DeviceMemory
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 ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
pPDeviceIndices' <- ((Ptr ("bindInfoCount" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("bindInfoCount" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("bindInfoCount" ::: Word32) -> IO b) -> IO b)
 -> ContT b IO (Ptr ("bindInfoCount" ::: Word32)))
-> ((Ptr ("bindInfoCount" ::: Word32) -> IO b) -> IO b)
-> ContT b IO (Ptr ("bindInfoCount" ::: Word32))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr ("bindInfoCount" ::: Word32) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Word32 ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4) 4
    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 -> ("bindInfoCount" ::: Word32) -> IO ())
-> Vector ("bindInfoCount" ::: Word32) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "bindInfoCount" ::: Word32
e -> Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("bindInfoCount" ::: Word32)
pPDeviceIndices' Ptr ("bindInfoCount" ::: Word32)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32) ("bindInfoCount" ::: Word32
e)) (Vector ("bindInfoCount" ::: Word32)
forall a. Monoid a => a
mempty)
    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 ("bindInfoCount" ::: Word32))
-> Ptr ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr (Ptr ("bindInfoCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr Word32))) (Ptr ("bindInfoCount" ::: Word32)
pPDeviceIndices')
    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 FromCStruct BindAccelerationStructureMemoryInfoKHR where
  peekCStruct :: ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> IO BindAccelerationStructureMemoryInfoKHR
peekCStruct p :: "pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p = do
    AccelerationStructureKHR
accelerationStructure <- ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureKHR (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR))
    DeviceMemory
memory <- Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceMemory))
    "dataSize" ::: Word64
memoryOffset <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize))
    "bindInfoCount" ::: Word32
deviceIndexCount <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32))
    Ptr ("bindInfoCount" ::: Word32)
pDeviceIndices <- Ptr (Ptr ("bindInfoCount" ::: Word32))
-> IO (Ptr ("bindInfoCount" ::: Word32))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Word32) (("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR
p ("pBindInfos" ::: Ptr BindAccelerationStructureMemoryInfoKHR)
-> Int -> Ptr (Ptr ("bindInfoCount" ::: Word32))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr Word32)))
    Vector ("bindInfoCount" ::: Word32)
pDeviceIndices' <- Int
-> (Int -> IO ("bindInfoCount" ::: Word32))
-> IO (Vector ("bindInfoCount" ::: Word32))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("bindInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "bindInfoCount" ::: Word32
deviceIndexCount) (\i :: Int
i -> Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr ("bindInfoCount" ::: Word32)
pDeviceIndices Ptr ("bindInfoCount" ::: Word32)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Word32)))
    BindAccelerationStructureMemoryInfoKHR
-> IO BindAccelerationStructureMemoryInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BindAccelerationStructureMemoryInfoKHR
 -> IO BindAccelerationStructureMemoryInfoKHR)
-> BindAccelerationStructureMemoryInfoKHR
-> IO BindAccelerationStructureMemoryInfoKHR
forall a b. (a -> b) -> a -> b
$ AccelerationStructureKHR
-> DeviceMemory
-> ("dataSize" ::: Word64)
-> Vector ("bindInfoCount" ::: Word32)
-> BindAccelerationStructureMemoryInfoKHR
BindAccelerationStructureMemoryInfoKHR
             AccelerationStructureKHR
accelerationStructure DeviceMemory
memory "dataSize" ::: Word64
memoryOffset Vector ("bindInfoCount" ::: Word32)
pDeviceIndices'

instance Zero BindAccelerationStructureMemoryInfoKHR where
  zero :: BindAccelerationStructureMemoryInfoKHR
zero = AccelerationStructureKHR
-> DeviceMemory
-> ("dataSize" ::: Word64)
-> Vector ("bindInfoCount" ::: Word32)
-> BindAccelerationStructureMemoryInfoKHR
BindAccelerationStructureMemoryInfoKHR
           AccelerationStructureKHR
forall a. Zero a => a
zero
           DeviceMemory
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           Vector ("bindInfoCount" ::: Word32)
forall a. Monoid a => a
mempty


-- | VkWriteDescriptorSetAccelerationStructureKHR - Structure specifying
-- acceleration structure descriptor info
--
-- == Valid Usage
--
-- -   @accelerationStructureCount@ /must/ be equal to @descriptorCount@ in
--     the extended structure
--
-- -   Each acceleration structure in @pAccelerationStructures@ /must/ have
--     been created with 'ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET_ACCELERATION_STRUCTURE_KHR'
--
-- -   @pAccelerationStructures@ /must/ be a valid pointer to an array of
--     @accelerationStructureCount@ valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handles
--
-- -   @accelerationStructureCount@ /must/ be greater than @0@
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data WriteDescriptorSetAccelerationStructureKHR = WriteDescriptorSetAccelerationStructureKHR
  { -- | @pAccelerationStructures@ are the acceleration structures to update.
    WriteDescriptorSetAccelerationStructureKHR
-> "accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures :: Vector AccelerationStructureKHR }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (WriteDescriptorSetAccelerationStructureKHR)
#endif
deriving instance Show WriteDescriptorSetAccelerationStructureKHR

instance ToCStruct WriteDescriptorSetAccelerationStructureKHR where
  withCStruct :: WriteDescriptorSetAccelerationStructureKHR
-> (Ptr WriteDescriptorSetAccelerationStructureKHR -> IO b) -> IO b
withCStruct x :: WriteDescriptorSetAccelerationStructureKHR
x f :: Ptr WriteDescriptorSetAccelerationStructureKHR -> IO b
f = Int
-> Int
-> (Ptr WriteDescriptorSetAccelerationStructureKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr WriteDescriptorSetAccelerationStructureKHR -> IO b) -> IO b)
-> (Ptr WriteDescriptorSetAccelerationStructureKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr WriteDescriptorSetAccelerationStructureKHR
p -> Ptr WriteDescriptorSetAccelerationStructureKHR
-> WriteDescriptorSetAccelerationStructureKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr WriteDescriptorSetAccelerationStructureKHR
p WriteDescriptorSetAccelerationStructureKHR
x (Ptr WriteDescriptorSetAccelerationStructureKHR -> IO b
f Ptr WriteDescriptorSetAccelerationStructureKHR
p)
  pokeCStruct :: Ptr WriteDescriptorSetAccelerationStructureKHR
-> WriteDescriptorSetAccelerationStructureKHR -> IO b -> IO b
pokeCStruct p :: Ptr WriteDescriptorSetAccelerationStructureKHR
p WriteDescriptorSetAccelerationStructureKHR{..} f :: 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 WriteDescriptorSetAccelerationStructureKHR
p Ptr WriteDescriptorSetAccelerationStructureKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET_ACCELERATION_STRUCTURE_KHR)
    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 WriteDescriptorSetAccelerationStructureKHR
p Ptr WriteDescriptorSetAccelerationStructureKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr WriteDescriptorSetAccelerationStructureKHR
p Ptr WriteDescriptorSetAccelerationStructureKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length (("accelerationStructures" ::: Vector AccelerationStructureKHR)
 -> Int)
-> ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> Int
forall a b. (a -> b) -> a -> b
$ ("accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures)) :: Word32))
    "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures' <- ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
  -> IO b)
 -> IO b)
-> ContT
     b IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO b)
  -> IO b)
 -> ContT
      b IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR))
-> ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
     -> IO b)
    -> IO b)
-> ContT
     b IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AccelerationStructureKHR ((("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> Int
forall a. Vector a -> Int
Data.Vector.length ("accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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 -> AccelerationStructureKHR -> IO ())
-> ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AccelerationStructureKHR
e -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures' ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AccelerationStructureKHR) (AccelerationStructureKHR
e)) ("accelerationStructures" ::: Vector AccelerationStructureKHR
accelerationStructures)
    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 ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr WriteDescriptorSetAccelerationStructureKHR
p Ptr WriteDescriptorSetAccelerationStructureKHR
-> Int
-> Ptr ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr AccelerationStructureKHR))) ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures')
    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 = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr WriteDescriptorSetAccelerationStructureKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr WriteDescriptorSetAccelerationStructureKHR
p f :: 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 WriteDescriptorSetAccelerationStructureKHR
p Ptr WriteDescriptorSetAccelerationStructureKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_WRITE_DESCRIPTOR_SET_ACCELERATION_STRUCTURE_KHR)
    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 WriteDescriptorSetAccelerationStructureKHR
p Ptr WriteDescriptorSetAccelerationStructureKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures' <- ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
  -> IO b)
 -> IO b)
-> ContT
     b IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
   -> IO b)
  -> IO b)
 -> ContT
      b IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR))
-> ((("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
     -> IO b)
    -> IO b)
-> ContT
     b IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AccelerationStructureKHR ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
    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 -> AccelerationStructureKHR -> IO ())
-> ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AccelerationStructureKHR
e -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures' ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AccelerationStructureKHR) (AccelerationStructureKHR
e)) ("accelerationStructures" ::: Vector AccelerationStructureKHR
forall a. Monoid a => a
mempty)
    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 ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr WriteDescriptorSetAccelerationStructureKHR
p Ptr WriteDescriptorSetAccelerationStructureKHR
-> Int
-> Ptr ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr AccelerationStructureKHR))) ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pPAccelerationStructures')
    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 FromCStruct WriteDescriptorSetAccelerationStructureKHR where
  peekCStruct :: Ptr WriteDescriptorSetAccelerationStructureKHR
-> IO WriteDescriptorSetAccelerationStructureKHR
peekCStruct p :: Ptr WriteDescriptorSetAccelerationStructureKHR
p = do
    "bindInfoCount" ::: Word32
accelerationStructureCount <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr WriteDescriptorSetAccelerationStructureKHR
p Ptr WriteDescriptorSetAccelerationStructureKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pAccelerationStructures <- Ptr ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr AccelerationStructureKHR) ((Ptr WriteDescriptorSetAccelerationStructureKHR
p Ptr WriteDescriptorSetAccelerationStructureKHR
-> Int
-> Ptr ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr AccelerationStructureKHR)))
    "accelerationStructures" ::: Vector AccelerationStructureKHR
pAccelerationStructures' <- Int
-> (Int -> IO AccelerationStructureKHR)
-> IO
     ("accelerationStructures" ::: Vector AccelerationStructureKHR)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("bindInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "bindInfoCount" ::: Word32
accelerationStructureCount) (\i :: Int
i -> ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureKHR (("pAccelerationStructures" ::: Ptr AccelerationStructureKHR
pAccelerationStructures ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AccelerationStructureKHR)))
    WriteDescriptorSetAccelerationStructureKHR
-> IO WriteDescriptorSetAccelerationStructureKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (WriteDescriptorSetAccelerationStructureKHR
 -> IO WriteDescriptorSetAccelerationStructureKHR)
-> WriteDescriptorSetAccelerationStructureKHR
-> IO WriteDescriptorSetAccelerationStructureKHR
forall a b. (a -> b) -> a -> b
$ ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> WriteDescriptorSetAccelerationStructureKHR
WriteDescriptorSetAccelerationStructureKHR
             "accelerationStructures" ::: Vector AccelerationStructureKHR
pAccelerationStructures'

instance Zero WriteDescriptorSetAccelerationStructureKHR where
  zero :: WriteDescriptorSetAccelerationStructureKHR
zero = ("accelerationStructures" ::: Vector AccelerationStructureKHR)
-> WriteDescriptorSetAccelerationStructureKHR
WriteDescriptorSetAccelerationStructureKHR
           "accelerationStructures" ::: Vector AccelerationStructureKHR
forall a. Monoid a => a
mempty


-- | VkAccelerationStructureMemoryRequirementsInfoKHR - Structure specifying
-- acceleration to query for memory requirements
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'AccelerationStructureBuildTypeKHR',
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'AccelerationStructureMemoryRequirementsTypeKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getAccelerationStructureMemoryRequirementsKHR'
data AccelerationStructureMemoryRequirementsInfoKHR = AccelerationStructureMemoryRequirementsInfoKHR
  { -- | @type@ selects the type of memory requirement being queried.
    -- 'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR' returns the
    -- memory requirements for the object itself.
    -- 'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR'
    -- returns the memory requirements for the scratch memory when doing a
    -- build.
    -- 'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR'
    -- returns the memory requirements for the scratch memory when doing an
    -- update.
    --
    -- @type@ /must/ be a valid
    -- 'AccelerationStructureMemoryRequirementsTypeKHR' value
    AccelerationStructureMemoryRequirementsInfoKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
type' :: AccelerationStructureMemoryRequirementsTypeKHR
  , -- | @buildType@ selects the build types whose memory requirements are being
    -- queried.
    --
    -- @buildType@ /must/ be a valid 'AccelerationStructureBuildTypeKHR' value
    AccelerationStructureMemoryRequirementsInfoKHR
-> AccelerationStructureBuildTypeKHR
buildType :: AccelerationStructureBuildTypeKHR
  , -- | @accelerationStructure@ is the acceleration structure to be queried for
    -- memory requirements.
    --
    -- @accelerationStructure@ /must/ be a valid
    -- 'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
    AccelerationStructureMemoryRequirementsInfoKHR
-> AccelerationStructureKHR
accelerationStructure :: AccelerationStructureKHR
  }
  deriving (Typeable, AccelerationStructureMemoryRequirementsInfoKHR
-> AccelerationStructureMemoryRequirementsInfoKHR -> Bool
(AccelerationStructureMemoryRequirementsInfoKHR
 -> AccelerationStructureMemoryRequirementsInfoKHR -> Bool)
-> (AccelerationStructureMemoryRequirementsInfoKHR
    -> AccelerationStructureMemoryRequirementsInfoKHR -> Bool)
-> Eq AccelerationStructureMemoryRequirementsInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureMemoryRequirementsInfoKHR
-> AccelerationStructureMemoryRequirementsInfoKHR -> Bool
$c/= :: AccelerationStructureMemoryRequirementsInfoKHR
-> AccelerationStructureMemoryRequirementsInfoKHR -> Bool
== :: AccelerationStructureMemoryRequirementsInfoKHR
-> AccelerationStructureMemoryRequirementsInfoKHR -> Bool
$c== :: AccelerationStructureMemoryRequirementsInfoKHR
-> AccelerationStructureMemoryRequirementsInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureMemoryRequirementsInfoKHR)
#endif
deriving instance Show AccelerationStructureMemoryRequirementsInfoKHR

instance ToCStruct AccelerationStructureMemoryRequirementsInfoKHR where
  withCStruct :: AccelerationStructureMemoryRequirementsInfoKHR
-> (("pInfo"
     ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
    -> IO b)
-> IO b
withCStruct x :: AccelerationStructureMemoryRequirementsInfoKHR
x f :: ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> IO b
f = Int
-> Int
-> (("pInfo"
     ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
  -> IO b)
 -> IO b)
-> (("pInfo"
     ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p -> ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> AccelerationStructureMemoryRequirementsInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p AccelerationStructureMemoryRequirementsInfoKHR
x (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> IO b
f "pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p)
  pokeCStruct :: ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> AccelerationStructureMemoryRequirementsInfoKHR -> IO b -> IO b
pokeCStruct p :: "pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p AccelerationStructureMemoryRequirementsInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr AccelerationStructureMemoryRequirementsTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureMemoryRequirementsTypeKHR)) (AccelerationStructureMemoryRequirementsTypeKHR
type')
    Ptr AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr AccelerationStructureBuildTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccelerationStructureBuildTypeKHR)) (AccelerationStructureBuildTypeKHR
buildType)
    ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
accelerationStructure)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> IO b -> IO b
pokeZeroCStruct p :: "pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr AccelerationStructureMemoryRequirementsTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureMemoryRequirementsTypeKHR)) (AccelerationStructureMemoryRequirementsTypeKHR
forall a. Zero a => a
zero)
    Ptr AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr AccelerationStructureBuildTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccelerationStructureBuildTypeKHR)) (AccelerationStructureBuildTypeKHR
forall a. Zero a => a
zero)
    ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct AccelerationStructureMemoryRequirementsInfoKHR where
  peekCStruct :: ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> IO AccelerationStructureMemoryRequirementsInfoKHR
peekCStruct p :: "pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p = do
    AccelerationStructureMemoryRequirementsTypeKHR
type' <- Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> IO AccelerationStructureMemoryRequirementsTypeKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureMemoryRequirementsTypeKHR (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr AccelerationStructureMemoryRequirementsTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureMemoryRequirementsTypeKHR))
    AccelerationStructureBuildTypeKHR
buildType <- Ptr AccelerationStructureBuildTypeKHR
-> IO AccelerationStructureBuildTypeKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureBuildTypeKHR (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int -> Ptr AccelerationStructureBuildTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr AccelerationStructureBuildTypeKHR))
    AccelerationStructureKHR
accelerationStructure <- ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureKHR (("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureMemoryRequirementsInfoKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureKHR))
    AccelerationStructureMemoryRequirementsInfoKHR
-> IO AccelerationStructureMemoryRequirementsInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AccelerationStructureMemoryRequirementsInfoKHR
 -> IO AccelerationStructureMemoryRequirementsInfoKHR)
-> AccelerationStructureMemoryRequirementsInfoKHR
-> IO AccelerationStructureMemoryRequirementsInfoKHR
forall a b. (a -> b) -> a -> b
$ AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureBuildTypeKHR
-> AccelerationStructureKHR
-> AccelerationStructureMemoryRequirementsInfoKHR
AccelerationStructureMemoryRequirementsInfoKHR
             AccelerationStructureMemoryRequirementsTypeKHR
type' AccelerationStructureBuildTypeKHR
buildType AccelerationStructureKHR
accelerationStructure

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

instance Zero AccelerationStructureMemoryRequirementsInfoKHR where
  zero :: AccelerationStructureMemoryRequirementsInfoKHR
zero = AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureBuildTypeKHR
-> AccelerationStructureKHR
-> AccelerationStructureMemoryRequirementsInfoKHR
AccelerationStructureMemoryRequirementsInfoKHR
           AccelerationStructureMemoryRequirementsTypeKHR
forall a. Zero a => a
zero
           AccelerationStructureBuildTypeKHR
forall a. Zero a => a
zero
           AccelerationStructureKHR
forall a. Zero a => a
zero


-- | VkPhysicalDeviceRayTracingFeaturesKHR - Structure describing the ray
-- tracing features that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDeviceRayTracingFeaturesKHR' structure
-- describe the following features:
--
-- = Description
--
-- -   @rayTracing@ indicates whether the implementation supports ray
--     tracing functionality. See
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#ray-tracing Ray Tracing>.
--
-- -   @rayTracingShaderGroupHandleCaptureReplay@ indicates whether the
--     implementation supports saving and reusing shader group handles,
--     e.g. for trace capture and replay.
--
-- -   @rayTracingShaderGroupHandleCaptureReplayMixed@ indicates whether
--     the implementation supports reuse of shader group handles being
--     arbitrarily mixed with creation of non-reused shader group handles.
--     If this is 'Vulkan.Core10.FundamentalTypes.FALSE', all reused shader
--     group handles /must/ be specified before any non-reused handles
--     /may/ be created.
--
-- -   @rayTracingAccelerationStructureCaptureReplay@ indicates whether the
--     implementation supports saving and reusing acceleration structure
--     device addresses, e.g. for trace capture and replay.
--
-- -   @rayTracingIndirectTraceRays@ indicates whether the implementation
--     supports indirect trace ray commands, e.g.
--     'cmdTraceRaysIndirectKHR'.
--
-- -   @rayTracingIndirectAccelerationStructureBuild@ indicates whether the
--     implementation supports indirect acceleration structure build
--     commands, e.g. 'cmdBuildAccelerationStructureIndirectKHR'.
--
-- -   @rayTracingHostAccelerationStructureCommands@ indicates whether the
--     implementation supports host side acceleration structure commands,
--     e.g. 'buildAccelerationStructureKHR',
--     'copyAccelerationStructureKHR',
--     'copyAccelerationStructureToMemoryKHR',
--     'copyMemoryToAccelerationStructureKHR',
--     'writeAccelerationStructuresPropertiesKHR'.
--
-- -   @rayQuery@ indicates whether the implementation supports ray query
--     (@OpRayQueryProceedKHR@) functionality.
--
-- -   @rayTracingPrimitiveCulling@ indicates whether the implementation
--     supports
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#ray-traversal-culling-primitive primitive culling during ray traversal>.
--
-- If the 'PhysicalDeviceRayTracingFeaturesKHR' structure is included in
-- the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceFeatures2',
-- it is filled with values indicating whether the feature is supported.
-- 'PhysicalDeviceRayTracingFeaturesKHR' /can/ also be used in the @pNext@
-- chain of 'Vulkan.Core10.Device.DeviceCreateInfo' to enable the features.
--
-- == Valid Usage
--
-- -   If @rayTracingShaderGroupHandleCaptureReplayMixed@ is
--     'Vulkan.Core10.FundamentalTypes.TRUE',
--     @rayTracingShaderGroupHandleCaptureReplay@ /must/ also be
--     'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_FEATURES_KHR'
--
-- = See Also
--
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceRayTracingFeaturesKHR = PhysicalDeviceRayTracingFeaturesKHR
  { -- No documentation found for Nested "VkPhysicalDeviceRayTracingFeaturesKHR" "rayTracing"
    PhysicalDeviceRayTracingFeaturesKHR -> Bool
rayTracing :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRayTracingFeaturesKHR" "rayTracingShaderGroupHandleCaptureReplay"
    PhysicalDeviceRayTracingFeaturesKHR -> Bool
rayTracingShaderGroupHandleCaptureReplay :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRayTracingFeaturesKHR" "rayTracingShaderGroupHandleCaptureReplayMixed"
    PhysicalDeviceRayTracingFeaturesKHR -> Bool
rayTracingShaderGroupHandleCaptureReplayMixed :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRayTracingFeaturesKHR" "rayTracingAccelerationStructureCaptureReplay"
    PhysicalDeviceRayTracingFeaturesKHR -> Bool
rayTracingAccelerationStructureCaptureReplay :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRayTracingFeaturesKHR" "rayTracingIndirectTraceRays"
    PhysicalDeviceRayTracingFeaturesKHR -> Bool
rayTracingIndirectTraceRays :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRayTracingFeaturesKHR" "rayTracingIndirectAccelerationStructureBuild"
    PhysicalDeviceRayTracingFeaturesKHR -> Bool
rayTracingIndirectAccelerationStructureBuild :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRayTracingFeaturesKHR" "rayTracingHostAccelerationStructureCommands"
    PhysicalDeviceRayTracingFeaturesKHR -> Bool
rayTracingHostAccelerationStructureCommands :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRayTracingFeaturesKHR" "rayQuery"
    PhysicalDeviceRayTracingFeaturesKHR -> Bool
rayQuery :: Bool
  , -- No documentation found for Nested "VkPhysicalDeviceRayTracingFeaturesKHR" "rayTracingPrimitiveCulling"
    PhysicalDeviceRayTracingFeaturesKHR -> Bool
rayTracingPrimitiveCulling :: Bool
  }
  deriving (Typeable, PhysicalDeviceRayTracingFeaturesKHR
-> PhysicalDeviceRayTracingFeaturesKHR -> Bool
(PhysicalDeviceRayTracingFeaturesKHR
 -> PhysicalDeviceRayTracingFeaturesKHR -> Bool)
-> (PhysicalDeviceRayTracingFeaturesKHR
    -> PhysicalDeviceRayTracingFeaturesKHR -> Bool)
-> Eq PhysicalDeviceRayTracingFeaturesKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceRayTracingFeaturesKHR
-> PhysicalDeviceRayTracingFeaturesKHR -> Bool
$c/= :: PhysicalDeviceRayTracingFeaturesKHR
-> PhysicalDeviceRayTracingFeaturesKHR -> Bool
== :: PhysicalDeviceRayTracingFeaturesKHR
-> PhysicalDeviceRayTracingFeaturesKHR -> Bool
$c== :: PhysicalDeviceRayTracingFeaturesKHR
-> PhysicalDeviceRayTracingFeaturesKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceRayTracingFeaturesKHR)
#endif
deriving instance Show PhysicalDeviceRayTracingFeaturesKHR

instance ToCStruct PhysicalDeviceRayTracingFeaturesKHR where
  withCStruct :: PhysicalDeviceRayTracingFeaturesKHR
-> (Ptr PhysicalDeviceRayTracingFeaturesKHR -> IO b) -> IO b
withCStruct x :: PhysicalDeviceRayTracingFeaturesKHR
x f :: Ptr PhysicalDeviceRayTracingFeaturesKHR -> IO b
f = Int
-> Int -> (Ptr PhysicalDeviceRayTracingFeaturesKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((Ptr PhysicalDeviceRayTracingFeaturesKHR -> IO b) -> IO b)
-> (Ptr PhysicalDeviceRayTracingFeaturesKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceRayTracingFeaturesKHR
p -> Ptr PhysicalDeviceRayTracingFeaturesKHR
-> PhysicalDeviceRayTracingFeaturesKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceRayTracingFeaturesKHR
p PhysicalDeviceRayTracingFeaturesKHR
x (Ptr PhysicalDeviceRayTracingFeaturesKHR -> IO b
f Ptr PhysicalDeviceRayTracingFeaturesKHR
p)
  pokeCStruct :: Ptr PhysicalDeviceRayTracingFeaturesKHR
-> PhysicalDeviceRayTracingFeaturesKHR -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceRayTracingFeaturesKHR
p PhysicalDeviceRayTracingFeaturesKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_FEATURES_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rayTracing))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rayTracingShaderGroupHandleCaptureReplay))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rayTracingShaderGroupHandleCaptureReplayMixed))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rayTracingAccelerationStructureCaptureReplay))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rayTracingIndirectTraceRays))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rayTracingIndirectAccelerationStructureBuild))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rayTracingHostAccelerationStructureCommands))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rayQuery))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
rayTracingPrimitiveCulling))
    IO b
f
  cStructSize :: Int
cStructSize = 56
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceRayTracingFeaturesKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceRayTracingFeaturesKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_FEATURES_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: 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 PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: 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 PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: 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 PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: 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 PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: 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 PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: 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 PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct PhysicalDeviceRayTracingFeaturesKHR where
  peekCStruct :: Ptr PhysicalDeviceRayTracingFeaturesKHR
-> IO PhysicalDeviceRayTracingFeaturesKHR
peekCStruct p :: Ptr PhysicalDeviceRayTracingFeaturesKHR
p = do
    Bool32
rayTracing <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32))
    Bool32
rayTracingShaderGroupHandleCaptureReplay <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Bool32))
    Bool32
rayTracingShaderGroupHandleCaptureReplayMixed <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32))
    Bool32
rayTracingAccelerationStructureCaptureReplay <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Bool32))
    Bool32
rayTracingIndirectTraceRays <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Bool32))
    Bool32
rayTracingIndirectAccelerationStructureBuild <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32))
    Bool32
rayTracingHostAccelerationStructureCommands <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Bool32))
    Bool32
rayQuery <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 44 :: Ptr Bool32))
    Bool32
rayTracingPrimitiveCulling <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr PhysicalDeviceRayTracingFeaturesKHR
p Ptr PhysicalDeviceRayTracingFeaturesKHR -> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32))
    PhysicalDeviceRayTracingFeaturesKHR
-> IO PhysicalDeviceRayTracingFeaturesKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceRayTracingFeaturesKHR
 -> IO PhysicalDeviceRayTracingFeaturesKHR)
-> PhysicalDeviceRayTracingFeaturesKHR
-> IO PhysicalDeviceRayTracingFeaturesKHR
forall a b. (a -> b) -> a -> b
$ Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> Bool
-> PhysicalDeviceRayTracingFeaturesKHR
PhysicalDeviceRayTracingFeaturesKHR
             (Bool32 -> Bool
bool32ToBool Bool32
rayTracing) (Bool32 -> Bool
bool32ToBool Bool32
rayTracingShaderGroupHandleCaptureReplay) (Bool32 -> Bool
bool32ToBool Bool32
rayTracingShaderGroupHandleCaptureReplayMixed) (Bool32 -> Bool
bool32ToBool Bool32
rayTracingAccelerationStructureCaptureReplay) (Bool32 -> Bool
bool32ToBool Bool32
rayTracingIndirectTraceRays) (Bool32 -> Bool
bool32ToBool Bool32
rayTracingIndirectAccelerationStructureBuild) (Bool32 -> Bool
bool32ToBool Bool32
rayTracingHostAccelerationStructureCommands) (Bool32 -> Bool
bool32ToBool Bool32
rayQuery) (Bool32 -> Bool
bool32ToBool Bool32
rayTracingPrimitiveCulling)

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

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


-- | VkPhysicalDeviceRayTracingPropertiesKHR - Properties of the physical
-- device for ray tracing
--
-- = Description
--
-- If the 'PhysicalDeviceRayTracingPropertiesKHR' structure is included in
-- the @pNext@ chain of
-- 'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.PhysicalDeviceProperties2',
-- it is filled with the implementation-dependent limits.
--
-- Limits specified by this structure /must/ match those specified with the
-- same name in
-- 'Vulkan.Extensions.VK_NV_ray_tracing.PhysicalDeviceRayTracingPropertiesNV'.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDeviceRayTracingPropertiesKHR = PhysicalDeviceRayTracingPropertiesKHR
  { -- | @shaderGroupHandleSize@ size in bytes of the shader header.
    PhysicalDeviceRayTracingPropertiesKHR -> "bindInfoCount" ::: Word32
shaderGroupHandleSize :: Word32
  , -- | @maxRecursionDepth@ is the maximum number of levels of recursion allowed
    -- in a trace command.
    PhysicalDeviceRayTracingPropertiesKHR -> "bindInfoCount" ::: Word32
maxRecursionDepth :: Word32
  , -- | @maxShaderGroupStride@ is the maximum stride in bytes allowed between
    -- shader groups in the SBT.
    PhysicalDeviceRayTracingPropertiesKHR -> "bindInfoCount" ::: Word32
maxShaderGroupStride :: Word32
  , -- | @shaderGroupBaseAlignment@ is the required alignment in bytes for the
    -- base of the SBTs.
    PhysicalDeviceRayTracingPropertiesKHR -> "bindInfoCount" ::: Word32
shaderGroupBaseAlignment :: Word32
  , -- | @maxGeometryCount@ is the maximum number of geometries in the bottom
    -- level acceleration structure.
    PhysicalDeviceRayTracingPropertiesKHR -> "dataSize" ::: Word64
maxGeometryCount :: Word64
  , -- | @maxInstanceCount@ is the maximum number of instances in the top level
    -- acceleration structure.
    PhysicalDeviceRayTracingPropertiesKHR -> "dataSize" ::: Word64
maxInstanceCount :: Word64
  , -- | @maxPrimitiveCount@ is the maximum number of triangles or AABBs in all
    -- geometries in the bottom level acceleration structure.
    PhysicalDeviceRayTracingPropertiesKHR -> "dataSize" ::: Word64
maxPrimitiveCount :: Word64
  , -- | @maxDescriptorSetAccelerationStructures@ is the maximum number of
    -- acceleration structure descriptors that are allowed in a descriptor set.
    PhysicalDeviceRayTracingPropertiesKHR -> "bindInfoCount" ::: Word32
maxDescriptorSetAccelerationStructures :: Word32
  , -- | @shaderGroupHandleCaptureReplaySize@ is the number of bytes for the
    -- information required to do capture and replay for shader group handles.
    PhysicalDeviceRayTracingPropertiesKHR -> "bindInfoCount" ::: Word32
shaderGroupHandleCaptureReplaySize :: Word32
  }
  deriving (Typeable, PhysicalDeviceRayTracingPropertiesKHR
-> PhysicalDeviceRayTracingPropertiesKHR -> Bool
(PhysicalDeviceRayTracingPropertiesKHR
 -> PhysicalDeviceRayTracingPropertiesKHR -> Bool)
-> (PhysicalDeviceRayTracingPropertiesKHR
    -> PhysicalDeviceRayTracingPropertiesKHR -> Bool)
-> Eq PhysicalDeviceRayTracingPropertiesKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDeviceRayTracingPropertiesKHR
-> PhysicalDeviceRayTracingPropertiesKHR -> Bool
$c/= :: PhysicalDeviceRayTracingPropertiesKHR
-> PhysicalDeviceRayTracingPropertiesKHR -> Bool
== :: PhysicalDeviceRayTracingPropertiesKHR
-> PhysicalDeviceRayTracingPropertiesKHR -> Bool
$c== :: PhysicalDeviceRayTracingPropertiesKHR
-> PhysicalDeviceRayTracingPropertiesKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDeviceRayTracingPropertiesKHR)
#endif
deriving instance Show PhysicalDeviceRayTracingPropertiesKHR

instance ToCStruct PhysicalDeviceRayTracingPropertiesKHR where
  withCStruct :: PhysicalDeviceRayTracingPropertiesKHR
-> (Ptr PhysicalDeviceRayTracingPropertiesKHR -> IO b) -> IO b
withCStruct x :: PhysicalDeviceRayTracingPropertiesKHR
x f :: Ptr PhysicalDeviceRayTracingPropertiesKHR -> IO b
f = Int
-> Int
-> (Ptr PhysicalDeviceRayTracingPropertiesKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr PhysicalDeviceRayTracingPropertiesKHR -> IO b) -> IO b)
-> (Ptr PhysicalDeviceRayTracingPropertiesKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PhysicalDeviceRayTracingPropertiesKHR
p -> Ptr PhysicalDeviceRayTracingPropertiesKHR
-> PhysicalDeviceRayTracingPropertiesKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PhysicalDeviceRayTracingPropertiesKHR
p PhysicalDeviceRayTracingPropertiesKHR
x (Ptr PhysicalDeviceRayTracingPropertiesKHR -> IO b
f Ptr PhysicalDeviceRayTracingPropertiesKHR
p)
  pokeCStruct :: Ptr PhysicalDeviceRayTracingPropertiesKHR
-> PhysicalDeviceRayTracingPropertiesKHR -> IO b -> IO b
pokeCStruct p :: Ptr PhysicalDeviceRayTracingPropertiesKHR
p PhysicalDeviceRayTracingPropertiesKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_PROPERTIES_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("bindInfoCount" ::: Word32
shaderGroupHandleSize)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("bindInfoCount" ::: Word32
maxRecursionDepth)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("bindInfoCount" ::: Word32
maxShaderGroupStride)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) ("bindInfoCount" ::: Word32
shaderGroupBaseAlignment)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word64)) ("dataSize" ::: Word64
maxGeometryCount)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word64)) ("dataSize" ::: Word64
maxInstanceCount)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word64)) ("dataSize" ::: Word64
maxPrimitiveCount)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) ("bindInfoCount" ::: Word32
maxDescriptorSetAccelerationStructures)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32)) ("bindInfoCount" ::: Word32
shaderGroupHandleCaptureReplaySize)
    IO b
f
  cStructSize :: Int
cStructSize = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr PhysicalDeviceRayTracingPropertiesKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr PhysicalDeviceRayTracingPropertiesKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PHYSICAL_DEVICE_RAY_TRACING_PROPERTIES_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word64)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word64)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word64)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PhysicalDeviceRayTracingPropertiesKHR where
  peekCStruct :: Ptr PhysicalDeviceRayTracingPropertiesKHR
-> IO PhysicalDeviceRayTracingPropertiesKHR
peekCStruct p :: Ptr PhysicalDeviceRayTracingPropertiesKHR
p = do
    "bindInfoCount" ::: Word32
shaderGroupHandleSize <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "bindInfoCount" ::: Word32
maxRecursionDepth <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    "bindInfoCount" ::: Word32
maxShaderGroupStride <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    "bindInfoCount" ::: Word32
shaderGroupBaseAlignment <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
    "dataSize" ::: Word64
maxGeometryCount <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word64))
    "dataSize" ::: Word64
maxInstanceCount <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word64))
    "dataSize" ::: Word64
maxPrimitiveCount <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word64))
    "bindInfoCount" ::: Word32
maxDescriptorSetAccelerationStructures <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32))
    "bindInfoCount" ::: Word32
shaderGroupHandleCaptureReplaySize <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDeviceRayTracingPropertiesKHR
p Ptr PhysicalDeviceRayTracingPropertiesKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 60 :: Ptr Word32))
    PhysicalDeviceRayTracingPropertiesKHR
-> IO PhysicalDeviceRayTracingPropertiesKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDeviceRayTracingPropertiesKHR
 -> IO PhysicalDeviceRayTracingPropertiesKHR)
-> PhysicalDeviceRayTracingPropertiesKHR
-> IO PhysicalDeviceRayTracingPropertiesKHR
forall a b. (a -> b) -> a -> b
$ ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> PhysicalDeviceRayTracingPropertiesKHR
PhysicalDeviceRayTracingPropertiesKHR
             "bindInfoCount" ::: Word32
shaderGroupHandleSize "bindInfoCount" ::: Word32
maxRecursionDepth "bindInfoCount" ::: Word32
maxShaderGroupStride "bindInfoCount" ::: Word32
shaderGroupBaseAlignment "dataSize" ::: Word64
maxGeometryCount "dataSize" ::: Word64
maxInstanceCount "dataSize" ::: Word64
maxPrimitiveCount "bindInfoCount" ::: Word32
maxDescriptorSetAccelerationStructures "bindInfoCount" ::: Word32
shaderGroupHandleCaptureReplaySize

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

instance Zero PhysicalDeviceRayTracingPropertiesKHR where
  zero :: PhysicalDeviceRayTracingPropertiesKHR
zero = ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> PhysicalDeviceRayTracingPropertiesKHR
PhysicalDeviceRayTracingPropertiesKHR
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero


-- | VkStridedBufferRegionKHR - Structure specifying a region of a VkBuffer
-- with a stride
--
-- == Valid Usage
--
-- -   If @buffer@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @size@
--     plus @offset@ /must/ be less than or equal to the size of @buffer@
--
-- -   If @buffer@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @stride@ /must/ be less than the size of @buffer@
--
-- == Valid Usage (Implicit)
--
-- -   If @buffer@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @buffer@ /must/ be a valid 'Vulkan.Core10.Handles.Buffer' handle
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Buffer',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize', 'cmdTraceRaysIndirectKHR',
-- 'cmdTraceRaysKHR'
data StridedBufferRegionKHR = StridedBufferRegionKHR
  { -- | @buffer@ is the buffer containing this region.
    ("raygenShaderBindingTable" ::: StridedBufferRegionKHR) -> Buffer
buffer :: Buffer
  , -- | @offset@ is the byte offset in @buffer@ at which the region starts.
    ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> "dataSize" ::: Word64
offset :: DeviceSize
  , -- | @stride@ is the byte stride between consecutive elements.
    ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> "dataSize" ::: Word64
stride :: DeviceSize
  , -- | @size@ is the size in bytes of the region starting at @offset@.
    ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> "dataSize" ::: Word64
size :: DeviceSize
  }
  deriving (Typeable, ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR) -> Bool
(("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
 -> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR) -> Bool)
-> (("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
    -> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR) -> Bool)
-> Eq ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR) -> Bool
$c/= :: ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR) -> Bool
== :: ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR) -> Bool
$c== :: ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR) -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (StridedBufferRegionKHR)
#endif
deriving instance Show StridedBufferRegionKHR

instance ToCStruct StridedBufferRegionKHR where
  withCStruct :: ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO b)
-> IO b
withCStruct x :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
x f :: ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> IO b
f = Int
-> Int
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((("pRaygenShaderBindingTable"
   ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
  -> IO b)
 -> IO b)
-> (("pRaygenShaderBindingTable"
     ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p -> ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> IO b
-> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p "raygenShaderBindingTable" ::: StridedBufferRegionKHR
x (("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> IO b
f "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p)
  pokeCStruct :: ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> IO b
-> IO b
pokeCStruct p :: "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p StridedBufferRegionKHR{..} f :: IO b
f = do
    Ptr Buffer -> Buffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Buffer)) (Buffer
buffer)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("dataSize" ::: Word64
offset)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("dataSize" ::: Word64
stride)
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("dataSize" ::: Word64
size)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> IO b -> IO b
pokeZeroCStruct p :: "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p f :: IO b
f = do
    Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: 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 (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("dataSize" ::: Word64
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct StridedBufferRegionKHR where
  peekCStruct :: ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> IO ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
peekCStruct p :: "pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p = do
    Buffer
buffer <- Ptr Buffer -> IO Buffer
forall a. Storable a => Ptr a -> IO a
peek @Buffer (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr Buffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Buffer))
    "dataSize" ::: Word64
offset <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize))
    "dataSize" ::: Word64
stride <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
    "dataSize" ::: Word64
size <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pRaygenShaderBindingTable"
::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
p ("pRaygenShaderBindingTable"
 ::: Ptr ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
    ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> IO ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
 -> IO ("raygenShaderBindingTable" ::: StridedBufferRegionKHR))
-> ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
-> IO ("raygenShaderBindingTable" ::: StridedBufferRegionKHR)
forall a b. (a -> b) -> a -> b
$ Buffer
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> "raygenShaderBindingTable" ::: StridedBufferRegionKHR
StridedBufferRegionKHR
             Buffer
buffer "dataSize" ::: Word64
offset "dataSize" ::: Word64
stride "dataSize" ::: Word64
size

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

instance Zero StridedBufferRegionKHR where
  zero :: "raygenShaderBindingTable" ::: StridedBufferRegionKHR
zero = Buffer
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> ("dataSize" ::: Word64)
-> "raygenShaderBindingTable" ::: StridedBufferRegionKHR
StridedBufferRegionKHR
           Buffer
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero


-- | VkTraceRaysIndirectCommandKHR - Structure specifying the parameters of
-- an indirect trace ray command
--
-- = Description
--
-- The members of 'TraceRaysIndirectCommandKHR' have the same meaning as
-- the similarly named parameters of 'cmdTraceRaysKHR'.
--
-- == Valid Usage
--
-- = See Also
--
-- No cross-references are available
data TraceRaysIndirectCommandKHR = TraceRaysIndirectCommandKHR
  { -- | @width@ is the width of the ray trace query dimensions.
    --
    -- @width@ /must/ be less than or equal to
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[0]
    TraceRaysIndirectCommandKHR -> "bindInfoCount" ::: Word32
width :: Word32
  , -- | @height@ is height of the ray trace query dimensions.
    --
    -- @height@ /must/ be less than or equal to
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[1]
    TraceRaysIndirectCommandKHR -> "bindInfoCount" ::: Word32
height :: Word32
  , -- | @depth@ is depth of the ray trace query dimensions.
    --
    -- @depth@ /must/ be less than or equal to
    -- 'Vulkan.Core10.DeviceInitialization.PhysicalDeviceLimits'::@maxComputeWorkGroupCount@[2]
    TraceRaysIndirectCommandKHR -> "bindInfoCount" ::: Word32
depth :: Word32
  }
  deriving (Typeable, TraceRaysIndirectCommandKHR -> TraceRaysIndirectCommandKHR -> Bool
(TraceRaysIndirectCommandKHR
 -> TraceRaysIndirectCommandKHR -> Bool)
-> (TraceRaysIndirectCommandKHR
    -> TraceRaysIndirectCommandKHR -> Bool)
-> Eq TraceRaysIndirectCommandKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TraceRaysIndirectCommandKHR -> TraceRaysIndirectCommandKHR -> Bool
$c/= :: TraceRaysIndirectCommandKHR -> TraceRaysIndirectCommandKHR -> Bool
== :: TraceRaysIndirectCommandKHR -> TraceRaysIndirectCommandKHR -> Bool
$c== :: TraceRaysIndirectCommandKHR -> TraceRaysIndirectCommandKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (TraceRaysIndirectCommandKHR)
#endif
deriving instance Show TraceRaysIndirectCommandKHR

instance ToCStruct TraceRaysIndirectCommandKHR where
  withCStruct :: TraceRaysIndirectCommandKHR
-> (Ptr TraceRaysIndirectCommandKHR -> IO b) -> IO b
withCStruct x :: TraceRaysIndirectCommandKHR
x f :: Ptr TraceRaysIndirectCommandKHR -> IO b
f = Int -> Int -> (Ptr TraceRaysIndirectCommandKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 12 4 ((Ptr TraceRaysIndirectCommandKHR -> IO b) -> IO b)
-> (Ptr TraceRaysIndirectCommandKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr TraceRaysIndirectCommandKHR
p -> Ptr TraceRaysIndirectCommandKHR
-> TraceRaysIndirectCommandKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr TraceRaysIndirectCommandKHR
p TraceRaysIndirectCommandKHR
x (Ptr TraceRaysIndirectCommandKHR -> IO b
f Ptr TraceRaysIndirectCommandKHR
p)
  pokeCStruct :: Ptr TraceRaysIndirectCommandKHR
-> TraceRaysIndirectCommandKHR -> IO b -> IO b
pokeCStruct p :: Ptr TraceRaysIndirectCommandKHR
p TraceRaysIndirectCommandKHR{..} f :: IO b
f = do
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TraceRaysIndirectCommandKHR
p Ptr TraceRaysIndirectCommandKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("bindInfoCount" ::: Word32
width)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TraceRaysIndirectCommandKHR
p Ptr TraceRaysIndirectCommandKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("bindInfoCount" ::: Word32
height)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TraceRaysIndirectCommandKHR
p Ptr TraceRaysIndirectCommandKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("bindInfoCount" ::: Word32
depth)
    IO b
f
  cStructSize :: Int
cStructSize = 12
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr TraceRaysIndirectCommandKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr TraceRaysIndirectCommandKHR
p f :: IO b
f = do
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TraceRaysIndirectCommandKHR
p Ptr TraceRaysIndirectCommandKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TraceRaysIndirectCommandKHR
p Ptr TraceRaysIndirectCommandKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr TraceRaysIndirectCommandKHR
p Ptr TraceRaysIndirectCommandKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct TraceRaysIndirectCommandKHR where
  peekCStruct :: Ptr TraceRaysIndirectCommandKHR -> IO TraceRaysIndirectCommandKHR
peekCStruct p :: Ptr TraceRaysIndirectCommandKHR
p = do
    "bindInfoCount" ::: Word32
width <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr TraceRaysIndirectCommandKHR
p Ptr TraceRaysIndirectCommandKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    "bindInfoCount" ::: Word32
height <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr TraceRaysIndirectCommandKHR
p Ptr TraceRaysIndirectCommandKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    "bindInfoCount" ::: Word32
depth <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr TraceRaysIndirectCommandKHR
p Ptr TraceRaysIndirectCommandKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    TraceRaysIndirectCommandKHR -> IO TraceRaysIndirectCommandKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TraceRaysIndirectCommandKHR -> IO TraceRaysIndirectCommandKHR)
-> TraceRaysIndirectCommandKHR -> IO TraceRaysIndirectCommandKHR
forall a b. (a -> b) -> a -> b
$ ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> TraceRaysIndirectCommandKHR
TraceRaysIndirectCommandKHR
             "bindInfoCount" ::: Word32
width "bindInfoCount" ::: Word32
height "bindInfoCount" ::: Word32
depth

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

instance Zero TraceRaysIndirectCommandKHR where
  zero :: TraceRaysIndirectCommandKHR
zero = ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> TraceRaysIndirectCommandKHR
TraceRaysIndirectCommandKHR
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero


-- | VkAccelerationStructureGeometryTrianglesDataKHR - Structure specifying a
-- triangle geometry in a bottom-level acceleration structure
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_TRIANGLES_DATA_KHR'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @vertexFormat@ /must/ be a valid 'Vulkan.Core10.Enums.Format.Format'
--     value
--
-- -   @vertexData@ /must/ be a valid 'DeviceOrHostAddressConstKHR' union
--
-- -   @indexType@ /must/ be a valid
--     'Vulkan.Core10.Enums.IndexType.IndexType' value
--
-- -   If @indexData@ is not @0@, @indexData@ /must/ be a valid
--     'DeviceOrHostAddressConstKHR' union
--
-- -   If @transformData@ is not @0@, @transformData@ /must/ be a valid
--     'DeviceOrHostAddressConstKHR' union
--
-- = See Also
--
-- 'AccelerationStructureGeometryDataKHR', 'DeviceOrHostAddressConstKHR',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.Format.Format',
-- 'Vulkan.Core10.Enums.IndexType.IndexType',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AccelerationStructureGeometryTrianglesDataKHR = AccelerationStructureGeometryTrianglesDataKHR
  { -- | @vertexFormat@ is the 'Vulkan.Core10.Enums.Format.Format' of each vertex
    -- element.
    AccelerationStructureGeometryTrianglesDataKHR -> Format
vertexFormat :: Format
  , -- | @vertexData@ is a device or host address to memory containing vertex
    -- data for this geometry.
    AccelerationStructureGeometryTrianglesDataKHR
-> DeviceOrHostAddressConstKHR
vertexData :: DeviceOrHostAddressConstKHR
  , -- | @vertexStride@ is the stride in bytes between each vertex.
    AccelerationStructureGeometryTrianglesDataKHR
-> "dataSize" ::: Word64
vertexStride :: DeviceSize
  , -- | @indexType@ is the 'Vulkan.Core10.Enums.IndexType.IndexType' of each
    -- index element.
    AccelerationStructureGeometryTrianglesDataKHR -> IndexType
indexType :: IndexType
  , -- | @indexData@ is a device or host address to memory containing index data
    -- for this geometry.
    AccelerationStructureGeometryTrianglesDataKHR
-> DeviceOrHostAddressConstKHR
indexData :: DeviceOrHostAddressConstKHR
  , -- | @transformData@ is a device or host address to memory containing an
    -- optional reference to a 'TransformMatrixKHR' structure defining a
    -- transformation that should be applied to vertices in this geometry.
    AccelerationStructureGeometryTrianglesDataKHR
-> DeviceOrHostAddressConstKHR
transformData :: DeviceOrHostAddressConstKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureGeometryTrianglesDataKHR)
#endif
deriving instance Show AccelerationStructureGeometryTrianglesDataKHR

instance ToCStruct AccelerationStructureGeometryTrianglesDataKHR where
  withCStruct :: AccelerationStructureGeometryTrianglesDataKHR
-> (Ptr AccelerationStructureGeometryTrianglesDataKHR -> IO b)
-> IO b
withCStruct x :: AccelerationStructureGeometryTrianglesDataKHR
x f :: Ptr AccelerationStructureGeometryTrianglesDataKHR -> IO b
f = Int
-> Int
-> (Ptr AccelerationStructureGeometryTrianglesDataKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr AccelerationStructureGeometryTrianglesDataKHR -> IO b)
 -> IO b)
-> (Ptr AccelerationStructureGeometryTrianglesDataKHR -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AccelerationStructureGeometryTrianglesDataKHR
p -> Ptr AccelerationStructureGeometryTrianglesDataKHR
-> AccelerationStructureGeometryTrianglesDataKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureGeometryTrianglesDataKHR
p AccelerationStructureGeometryTrianglesDataKHR
x (Ptr AccelerationStructureGeometryTrianglesDataKHR -> IO b
f Ptr AccelerationStructureGeometryTrianglesDataKHR
p)
  pokeCStruct :: Ptr AccelerationStructureGeometryTrianglesDataKHR
-> AccelerationStructureGeometryTrianglesDataKHR -> IO b -> IO b
pokeCStruct p :: Ptr AccelerationStructureGeometryTrianglesDataKHR
p AccelerationStructureGeometryTrianglesDataKHR{..} f :: 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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_TRIANGLES_DATA_KHR)
    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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format)) (Format
vertexFormat)
    ((() -> 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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
vertexData) (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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) ("dataSize" ::: Word64
vertexStride)
    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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr IndexType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: 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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
indexData) (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 ((Ptr AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceOrHostAddressConstKHR)) (DeviceOrHostAddressConstKHR
transformData) (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 -> 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 = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr AccelerationStructureGeometryTrianglesDataKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AccelerationStructureGeometryTrianglesDataKHR
p f :: 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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_TRIANGLES_DATA_KHR)
    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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Format)) (Format
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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 IndexType -> IndexType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureGeometryTrianglesDataKHR
p Ptr AccelerationStructureGeometryTrianglesDataKHR
-> Int -> Ptr IndexType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr IndexType)) (IndexType
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 AccelerationStructureGeometryTrianglesDataKHR where
  zero :: AccelerationStructureGeometryTrianglesDataKHR
zero = Format
-> DeviceOrHostAddressConstKHR
-> ("dataSize" ::: Word64)
-> IndexType
-> DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR
-> AccelerationStructureGeometryTrianglesDataKHR
AccelerationStructureGeometryTrianglesDataKHR
           Format
forall a. Zero a => a
zero
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           IndexType
forall a. Zero a => a
zero
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero


-- | VkAccelerationStructureGeometryAabbsDataKHR - Structure specifying
-- axis-aligned bounding box geometry in a bottom-level acceleration
-- structure
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'AccelerationStructureGeometryDataKHR', 'DeviceOrHostAddressConstKHR',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AccelerationStructureGeometryAabbsDataKHR = AccelerationStructureGeometryAabbsDataKHR
  { -- | @data@ is a device or host address to memory containing
    -- 'AabbPositionsKHR' structures containing position data for each
    -- axis-aligned bounding box in the geometry.
    --
    -- @data@ /must/ be aligned to @8@ bytes
    --
    -- @data@ /must/ be a valid 'DeviceOrHostAddressConstKHR' union
    AccelerationStructureGeometryAabbsDataKHR
-> DeviceOrHostAddressConstKHR
data' :: DeviceOrHostAddressConstKHR
  , -- | @stride@ is the stride in bytes between each entry in @data@.
    --
    -- @stride@ /must/ be a multiple of @8@
    AccelerationStructureGeometryAabbsDataKHR -> "dataSize" ::: Word64
stride :: DeviceSize
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureGeometryAabbsDataKHR)
#endif
deriving instance Show AccelerationStructureGeometryAabbsDataKHR

instance ToCStruct AccelerationStructureGeometryAabbsDataKHR where
  withCStruct :: AccelerationStructureGeometryAabbsDataKHR
-> (Ptr AccelerationStructureGeometryAabbsDataKHR -> IO b) -> IO b
withCStruct x :: AccelerationStructureGeometryAabbsDataKHR
x f :: Ptr AccelerationStructureGeometryAabbsDataKHR -> IO b
f = Int
-> Int
-> (Ptr AccelerationStructureGeometryAabbsDataKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr AccelerationStructureGeometryAabbsDataKHR -> IO b) -> IO b)
-> (Ptr AccelerationStructureGeometryAabbsDataKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AccelerationStructureGeometryAabbsDataKHR
p -> Ptr AccelerationStructureGeometryAabbsDataKHR
-> AccelerationStructureGeometryAabbsDataKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureGeometryAabbsDataKHR
p AccelerationStructureGeometryAabbsDataKHR
x (Ptr AccelerationStructureGeometryAabbsDataKHR -> IO b
f Ptr AccelerationStructureGeometryAabbsDataKHR
p)
  pokeCStruct :: Ptr AccelerationStructureGeometryAabbsDataKHR
-> AccelerationStructureGeometryAabbsDataKHR -> IO b -> IO b
pokeCStruct p :: Ptr AccelerationStructureGeometryAabbsDataKHR
p AccelerationStructureGeometryAabbsDataKHR{..} f :: 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 AccelerationStructureGeometryAabbsDataKHR
p Ptr AccelerationStructureGeometryAabbsDataKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_AABBS_DATA_KHR)
    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 AccelerationStructureGeometryAabbsDataKHR
p Ptr AccelerationStructureGeometryAabbsDataKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 AccelerationStructureGeometryAabbsDataKHR
p Ptr AccelerationStructureGeometryAabbsDataKHR
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: 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 () -> 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 AccelerationStructureGeometryAabbsDataKHR
p Ptr AccelerationStructureGeometryAabbsDataKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("dataSize" ::: Word64
stride)
    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 = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr AccelerationStructureGeometryAabbsDataKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AccelerationStructureGeometryAabbsDataKHR
p f :: 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 AccelerationStructureGeometryAabbsDataKHR
p Ptr AccelerationStructureGeometryAabbsDataKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_AABBS_DATA_KHR)
    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 AccelerationStructureGeometryAabbsDataKHR
p Ptr AccelerationStructureGeometryAabbsDataKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 AccelerationStructureGeometryAabbsDataKHR
p Ptr AccelerationStructureGeometryAabbsDataKHR
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureGeometryAabbsDataKHR
p Ptr AccelerationStructureGeometryAabbsDataKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: 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 AccelerationStructureGeometryAabbsDataKHR where
  zero :: AccelerationStructureGeometryAabbsDataKHR
zero = DeviceOrHostAddressConstKHR
-> ("dataSize" ::: Word64)
-> AccelerationStructureGeometryAabbsDataKHR
AccelerationStructureGeometryAabbsDataKHR
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero


-- | VkAccelerationStructureGeometryInstancesDataKHR - Structure specifying a
-- geometry consisting of instances of other acceleration structures
--
-- == Valid Usage
--
-- -   @data@ /must/ be aligned to @16@ bytes
--
-- -   If @arrayOfPointers@ is true, each pointer /must/ be aligned to @16@
--     bytes
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_INSTANCES_DATA_KHR'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @data@ /must/ be a valid 'DeviceOrHostAddressConstKHR' union
--
-- = See Also
--
-- 'AccelerationStructureGeometryDataKHR',
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'DeviceOrHostAddressConstKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AccelerationStructureGeometryInstancesDataKHR = AccelerationStructureGeometryInstancesDataKHR
  { -- | @arrayOfPointers@ specifies whether @data@ is used as an array of
    -- addresses or just an array.
    AccelerationStructureGeometryInstancesDataKHR -> Bool
arrayOfPointers :: Bool
  , -- | @data@ is either the address of an array of device or host addresses
    -- referencing individual 'AccelerationStructureInstanceKHR' structures if
    -- @arrayOfPointers@ is 'Vulkan.Core10.FundamentalTypes.TRUE', or the
    -- address of an array of 'AccelerationStructureInstanceKHR' structures.
    AccelerationStructureGeometryInstancesDataKHR
-> DeviceOrHostAddressConstKHR
data' :: DeviceOrHostAddressConstKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureGeometryInstancesDataKHR)
#endif
deriving instance Show AccelerationStructureGeometryInstancesDataKHR

instance ToCStruct AccelerationStructureGeometryInstancesDataKHR where
  withCStruct :: AccelerationStructureGeometryInstancesDataKHR
-> (Ptr AccelerationStructureGeometryInstancesDataKHR -> IO b)
-> IO b
withCStruct x :: AccelerationStructureGeometryInstancesDataKHR
x f :: Ptr AccelerationStructureGeometryInstancesDataKHR -> IO b
f = Int
-> Int
-> (Ptr AccelerationStructureGeometryInstancesDataKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr AccelerationStructureGeometryInstancesDataKHR -> IO b)
 -> IO b)
-> (Ptr AccelerationStructureGeometryInstancesDataKHR -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AccelerationStructureGeometryInstancesDataKHR
p -> Ptr AccelerationStructureGeometryInstancesDataKHR
-> AccelerationStructureGeometryInstancesDataKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureGeometryInstancesDataKHR
p AccelerationStructureGeometryInstancesDataKHR
x (Ptr AccelerationStructureGeometryInstancesDataKHR -> IO b
f Ptr AccelerationStructureGeometryInstancesDataKHR
p)
  pokeCStruct :: Ptr AccelerationStructureGeometryInstancesDataKHR
-> AccelerationStructureGeometryInstancesDataKHR -> IO b -> IO b
pokeCStruct p :: Ptr AccelerationStructureGeometryInstancesDataKHR
p AccelerationStructureGeometryInstancesDataKHR{..} f :: 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 AccelerationStructureGeometryInstancesDataKHR
p Ptr AccelerationStructureGeometryInstancesDataKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_INSTANCES_DATA_KHR)
    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 AccelerationStructureGeometryInstancesDataKHR
p Ptr AccelerationStructureGeometryInstancesDataKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureGeometryInstancesDataKHR
p Ptr AccelerationStructureGeometryInstancesDataKHR
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
arrayOfPointers))
    ((() -> 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 AccelerationStructureGeometryInstancesDataKHR
p Ptr AccelerationStructureGeometryInstancesDataKHR
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: 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 -> 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 = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr AccelerationStructureGeometryInstancesDataKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AccelerationStructureGeometryInstancesDataKHR
p f :: 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 AccelerationStructureGeometryInstancesDataKHR
p Ptr AccelerationStructureGeometryInstancesDataKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_INSTANCES_DATA_KHR)
    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 AccelerationStructureGeometryInstancesDataKHR
p Ptr AccelerationStructureGeometryInstancesDataKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureGeometryInstancesDataKHR
p Ptr AccelerationStructureGeometryInstancesDataKHR
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
forall a. Zero a => a
zero))
    ((() -> IO b) -> 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 AccelerationStructureGeometryInstancesDataKHR
p Ptr AccelerationStructureGeometryInstancesDataKHR
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 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 AccelerationStructureGeometryInstancesDataKHR where
  zero :: AccelerationStructureGeometryInstancesDataKHR
zero = Bool
-> DeviceOrHostAddressConstKHR
-> AccelerationStructureGeometryInstancesDataKHR
AccelerationStructureGeometryInstancesDataKHR
           Bool
forall a. Zero a => a
zero
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero


-- | VkAccelerationStructureGeometryKHR - Structure specifying geometries to
-- be built into an acceleration structure
--
-- == Valid Usage
--
-- -   If @geometryType@ is 'GEOMETRY_TYPE_AABBS_KHR', the @aabbs@ member
--     of @geometry@ /must/ be a valid
--     'AccelerationStructureGeometryAabbsDataKHR' structure
--
-- -   If @geometryType@ is 'GEOMETRY_TYPE_TRIANGLES_KHR', the @triangles@
--     member of @geometry@ /must/ be a valid
--     'AccelerationStructureGeometryTrianglesDataKHR' structure
--
-- -   If @geometryType@ is 'GEOMETRY_TYPE_INSTANCES_KHR', the @instances@
--     member of @geometry@ /must/ be a valid
--     'AccelerationStructureGeometryInstancesDataKHR' structure
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_KHR'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @geometryType@ /must/ be a valid 'GeometryTypeKHR' value
--
-- -   If @geometryType@ is 'GEOMETRY_TYPE_TRIANGLES_KHR', the @triangles@
--     member of @geometry@ /must/ be a valid
--     'AccelerationStructureGeometryTrianglesDataKHR' structure
--
-- -   If @geometryType@ is 'GEOMETRY_TYPE_AABBS_KHR', the @aabbs@ member
--     of @geometry@ /must/ be a valid
--     'AccelerationStructureGeometryAabbsDataKHR' structure
--
-- -   If @geometryType@ is 'GEOMETRY_TYPE_INSTANCES_KHR', the @instances@
--     member of @geometry@ /must/ be a valid
--     'AccelerationStructureGeometryInstancesDataKHR' structure
--
-- -   @flags@ /must/ be a valid combination of 'GeometryFlagBitsKHR'
--     values
--
-- = See Also
--
-- 'AccelerationStructureBuildGeometryInfoKHR',
-- 'AccelerationStructureGeometryDataKHR', 'GeometryFlagsKHR',
-- 'GeometryTypeKHR', 'Vulkan.Core10.Enums.StructureType.StructureType'
data AccelerationStructureGeometryKHR = AccelerationStructureGeometryKHR
  { -- | @geometryType@ describes which type of geometry this
    -- 'AccelerationStructureGeometryKHR' refers to.
    AccelerationStructureGeometryKHR -> GeometryTypeKHR
geometryType :: GeometryTypeKHR
  , -- | @geometry@ is a 'AccelerationStructureGeometryDataKHR' union describing
    -- the geometry data for the relevant geometry type.
    AccelerationStructureGeometryKHR
-> AccelerationStructureGeometryDataKHR
geometry :: AccelerationStructureGeometryDataKHR
  , -- | @flags@ is a bitmask of 'GeometryFlagBitsKHR' values describing
    -- additional properties of how the geometry should be built.
    AccelerationStructureGeometryKHR -> GeometryFlagsKHR
flags :: GeometryFlagsKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureGeometryKHR)
#endif
deriving instance Show AccelerationStructureGeometryKHR

instance ToCStruct AccelerationStructureGeometryKHR where
  withCStruct :: AccelerationStructureGeometryKHR
-> (Ptr AccelerationStructureGeometryKHR -> IO b) -> IO b
withCStruct x :: AccelerationStructureGeometryKHR
x f :: Ptr AccelerationStructureGeometryKHR -> IO b
f = Int
-> Int -> (Ptr AccelerationStructureGeometryKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 96 8 ((Ptr AccelerationStructureGeometryKHR -> IO b) -> IO b)
-> (Ptr AccelerationStructureGeometryKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AccelerationStructureGeometryKHR
p -> Ptr AccelerationStructureGeometryKHR
-> AccelerationStructureGeometryKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureGeometryKHR
p AccelerationStructureGeometryKHR
x (Ptr AccelerationStructureGeometryKHR -> IO b
f Ptr AccelerationStructureGeometryKHR
p)
  pokeCStruct :: Ptr AccelerationStructureGeometryKHR
-> AccelerationStructureGeometryKHR -> IO b -> IO b
pokeCStruct p :: Ptr AccelerationStructureGeometryKHR
p AccelerationStructureGeometryKHR{..} f :: 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 AccelerationStructureGeometryKHR
p Ptr AccelerationStructureGeometryKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_KHR)
    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 AccelerationStructureGeometryKHR
p Ptr AccelerationStructureGeometryKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 GeometryTypeKHR -> GeometryTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureGeometryKHR
p Ptr AccelerationStructureGeometryKHR -> Int -> Ptr GeometryTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr GeometryTypeKHR)) (GeometryTypeKHR
geometryType)
    ((() -> 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 AccelerationStructureGeometryDataKHR
-> AccelerationStructureGeometryDataKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr AccelerationStructureGeometryKHR
p Ptr AccelerationStructureGeometryKHR
-> Int -> Ptr AccelerationStructureGeometryDataKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureGeometryDataKHR)) (AccelerationStructureGeometryDataKHR
geometry) (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 GeometryFlagsKHR -> GeometryFlagsKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureGeometryKHR
p Ptr AccelerationStructureGeometryKHR -> Int -> Ptr GeometryFlagsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr GeometryFlagsKHR)) (GeometryFlagsKHR
flags)
    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 = 96
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr AccelerationStructureGeometryKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AccelerationStructureGeometryKHR
p f :: 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 AccelerationStructureGeometryKHR
p Ptr AccelerationStructureGeometryKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_GEOMETRY_KHR)
    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 AccelerationStructureGeometryKHR
p Ptr AccelerationStructureGeometryKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 GeometryTypeKHR -> GeometryTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureGeometryKHR
p Ptr AccelerationStructureGeometryKHR -> Int -> Ptr GeometryTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr GeometryTypeKHR)) (GeometryTypeKHR
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 AccelerationStructureGeometryDataKHR
-> AccelerationStructureGeometryDataKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr AccelerationStructureGeometryKHR
p Ptr AccelerationStructureGeometryKHR
-> Int -> Ptr AccelerationStructureGeometryDataKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureGeometryDataKHR)) (AccelerationStructureGeometryDataKHR
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 -> 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 AccelerationStructureGeometryKHR where
  zero :: AccelerationStructureGeometryKHR
zero = GeometryTypeKHR
-> AccelerationStructureGeometryDataKHR
-> GeometryFlagsKHR
-> AccelerationStructureGeometryKHR
AccelerationStructureGeometryKHR
           GeometryTypeKHR
forall a. Zero a => a
zero
           AccelerationStructureGeometryDataKHR
forall a. Zero a => a
zero
           GeometryFlagsKHR
forall a. Zero a => a
zero


-- | VkAccelerationStructureBuildGeometryInfoKHR - Structure specifying the
-- geometry data used to build an acceleration structure
--
-- = Description
--
-- Note
--
-- Elements of @ppGeometries@ are accessed as follows, based on
-- @geometryArrayOfPointers@:
--
-- > if (geometryArrayOfPointers) {
-- >     use *(ppGeometries[i]);
-- > } else {
-- >     use (*ppGeometries)[i];
-- > }
--
-- == Valid Usage
--
-- -   If @update@ is 'Vulkan.Core10.FundamentalTypes.TRUE',
--     @srcAccelerationStructure@ /must/ not be
--     'Vulkan.Core10.APIConstants.NULL_HANDLE'
--
-- -   If @update@ is 'Vulkan.Core10.FundamentalTypes.TRUE',
--     @srcAccelerationStructure@ /must/ have been built before with
--     'BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR' set in
--     'AccelerationStructureBuildGeometryInfoKHR'::@flags@
--
-- -   @scratchData@ /must/ have been created with
--     'Vulkan.Core10.Enums.BufferUsageFlagBits.BUFFER_USAGE_RAY_TRACING_BIT_KHR'
--     usage flag
--
-- -   If @update@ is 'Vulkan.Core10.FundamentalTypes.TRUE', the
--     @srcAccelerationStructure@ and @dstAccelerationStructure@ objects
--     /must/ either be the same object or not have any
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#resources-memory-aliasing memory aliasing>
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ACCELERATION_STRUCTURE_BUILD_GEOMETRY_INFO_KHR'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @type@ /must/ be a valid 'AccelerationStructureTypeKHR' value
--
-- -   @flags@ /must/ be a valid combination of
--     'BuildAccelerationStructureFlagBitsKHR' values
--
-- -   If @srcAccelerationStructure@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @srcAccelerationStructure@
--     /must/ be a valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
--
-- -   @dstAccelerationStructure@ /must/ be a valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
--
-- -   @scratchData@ /must/ be a valid 'DeviceOrHostAddressKHR' union
--
-- -   Both of @dstAccelerationStructure@, and @srcAccelerationStructure@
--     that are valid handles of non-ignored parameters /must/ have been
--     created, allocated, or retrieved from the same
--     'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'AccelerationStructureGeometryKHR',
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'AccelerationStructureTypeKHR', 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'BuildAccelerationStructureFlagsKHR', 'DeviceOrHostAddressKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'buildAccelerationStructureKHR',
-- 'cmdBuildAccelerationStructureIndirectKHR',
-- 'cmdBuildAccelerationStructureKHR'
data AccelerationStructureBuildGeometryInfoKHR (es :: [Type]) = AccelerationStructureBuildGeometryInfoKHR
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    AccelerationStructureBuildGeometryInfoKHR es -> Chain es
next :: Chain es
  , -- | @type@ is a 'AccelerationStructureTypeKHR' value specifying the type of
    -- acceleration structure being built.
    AccelerationStructureBuildGeometryInfoKHR es
-> AccelerationStructureTypeKHR
type' :: AccelerationStructureTypeKHR
  , -- | @flags@ is a bitmask of 'BuildAccelerationStructureFlagBitsKHR'
    -- specifying additional parameters of the acceleration structure.
    AccelerationStructureBuildGeometryInfoKHR es
-> BuildAccelerationStructureFlagsKHR
flags :: BuildAccelerationStructureFlagsKHR
  , -- | @update@ specifies whether to update @dstAccelerationStructure@ with the
    -- data in @srcAccelerationStructure@ or not.
    AccelerationStructureBuildGeometryInfoKHR es -> Bool
update :: Bool
  , -- | @srcAccelerationStructure@ points to an existing acceleration structure
    -- that is to be used to update the @dst@ acceleration structure when
    -- @update@ is 'Vulkan.Core10.FundamentalTypes.TRUE'.
    AccelerationStructureBuildGeometryInfoKHR es
-> AccelerationStructureKHR
srcAccelerationStructure :: AccelerationStructureKHR
  , -- | @dstAccelerationStructure@ points to the target acceleration structure
    -- for the build.
    AccelerationStructureBuildGeometryInfoKHR es
-> AccelerationStructureKHR
dstAccelerationStructure :: AccelerationStructureKHR
  , -- | @ppGeometries@ is either a pointer to an array of pointers to
    -- 'AccelerationStructureGeometryKHR' structures if
    -- @geometryArrayOfPointers@ is 'Vulkan.Core10.FundamentalTypes.TRUE', or a
    -- pointer to a pointer to an array of 'AccelerationStructureGeometryKHR'
    -- structures if it is 'Vulkan.Core10.FundamentalTypes.FALSE'. Each element
    -- of the array describes the data used to build each acceleration
    -- structure geometry.
    AccelerationStructureBuildGeometryInfoKHR es
-> Vector AccelerationStructureGeometryKHR
geometries :: Vector AccelerationStructureGeometryKHR
  , -- | @scratchData@ is the device or host address to memory that will be used
    -- as scratch memory for the build.
    AccelerationStructureBuildGeometryInfoKHR es
-> DeviceOrHostAddressKHR
scratchData :: DeviceOrHostAddressKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureBuildGeometryInfoKHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (AccelerationStructureBuildGeometryInfoKHR es)

instance Extensible AccelerationStructureBuildGeometryInfoKHR where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_BUILD_GEOMETRY_INFO_KHR
  setNext :: AccelerationStructureBuildGeometryInfoKHR ds
-> Chain es -> AccelerationStructureBuildGeometryInfoKHR es
setNext x :: AccelerationStructureBuildGeometryInfoKHR ds
x next :: Chain es
next = AccelerationStructureBuildGeometryInfoKHR ds
x{$sel:next:AccelerationStructureBuildGeometryInfoKHR :: Chain es
next = Chain es
next}
  getNext :: AccelerationStructureBuildGeometryInfoKHR es -> Chain es
getNext AccelerationStructureBuildGeometryInfoKHR{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends AccelerationStructureBuildGeometryInfoKHR e => b) -> Maybe b
  extends :: proxy e
-> (Extends AccelerationStructureBuildGeometryInfoKHR e => b)
-> Maybe b
extends _ f :: Extends AccelerationStructureBuildGeometryInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable DeferredOperationInfoKHR) =>
Maybe (e :~: DeferredOperationInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeferredOperationInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends AccelerationStructureBuildGeometryInfoKHR e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss AccelerationStructureBuildGeometryInfoKHR es, PokeChain es) => ToCStruct (AccelerationStructureBuildGeometryInfoKHR es) where
  withCStruct :: AccelerationStructureBuildGeometryInfoKHR es
-> (Ptr (AccelerationStructureBuildGeometryInfoKHR es) -> IO b)
-> IO b
withCStruct x :: AccelerationStructureBuildGeometryInfoKHR es
x f :: Ptr (AccelerationStructureBuildGeometryInfoKHR es) -> IO b
f = Int
-> Int
-> (Ptr (AccelerationStructureBuildGeometryInfoKHR es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 72 8 ((Ptr (AccelerationStructureBuildGeometryInfoKHR es) -> IO b)
 -> IO b)
-> (Ptr (AccelerationStructureBuildGeometryInfoKHR es) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p -> Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> AccelerationStructureBuildGeometryInfoKHR es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p AccelerationStructureBuildGeometryInfoKHR es
x (Ptr (AccelerationStructureBuildGeometryInfoKHR es) -> IO b
f Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p)
  pokeCStruct :: Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> AccelerationStructureBuildGeometryInfoKHR es -> IO b -> IO b
pokeCStruct p :: Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p AccelerationStructureBuildGeometryInfoKHR{..} f :: 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 (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_BUILD_GEOMETRY_INFO_KHR)
    "data" ::: Ptr ()
pNext'' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    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 (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext''
    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 AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr AccelerationStructureTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureTypeKHR)) (AccelerationStructureTypeKHR
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 BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr BuildAccelerationStructureFlagsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr BuildAccelerationStructureFlagsKHR)) (BuildAccelerationStructureFlagsKHR
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 Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
update))
    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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
srcAccelerationStructure)
    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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
dstAccelerationStructure)
    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 Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Bool32)) (Bool32
FALSE)
    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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector AccelerationStructureGeometryKHR -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AccelerationStructureGeometryKHR -> Int)
-> Vector AccelerationStructureGeometryKHR -> Int
forall a b. (a -> b) -> a -> b
$ (Vector AccelerationStructureGeometryKHR
geometries)) :: Word32))
    Ptr AccelerationStructureGeometryKHR
pPpGeometries' <- ((Ptr AccelerationStructureGeometryKHR -> IO b) -> IO b)
-> ContT b IO (Ptr AccelerationStructureGeometryKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AccelerationStructureGeometryKHR -> IO b) -> IO b)
 -> ContT b IO (Ptr AccelerationStructureGeometryKHR))
-> ((Ptr AccelerationStructureGeometryKHR -> IO b) -> IO b)
-> ContT b IO (Ptr AccelerationStructureGeometryKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int -> (Ptr AccelerationStructureGeometryKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AccelerationStructureGeometryKHR ((Vector AccelerationStructureGeometryKHR -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AccelerationStructureGeometryKHR
geometries)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 96) 8
    (Int -> AccelerationStructureGeometryKHR -> ContT b IO ())
-> Vector AccelerationStructureGeometryKHR -> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AccelerationStructureGeometryKHR
e -> ((() -> 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 AccelerationStructureGeometryKHR
-> AccelerationStructureGeometryKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AccelerationStructureGeometryKHR
pPpGeometries' Ptr AccelerationStructureGeometryKHR
-> Int -> Ptr AccelerationStructureGeometryKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (96 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AccelerationStructureGeometryKHR) (AccelerationStructureGeometryKHR
e) (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
$ ())) (Vector AccelerationStructureGeometryKHR
geometries)
    Ptr (Ptr AccelerationStructureGeometryKHR)
ppGeometries'' <- ((Ptr (Ptr AccelerationStructureGeometryKHR) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr AccelerationStructureGeometryKHR))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Ptr AccelerationStructureGeometryKHR) -> IO b) -> IO b)
 -> ContT b IO (Ptr (Ptr AccelerationStructureGeometryKHR)))
-> ((Ptr (Ptr AccelerationStructureGeometryKHR) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr AccelerationStructureGeometryKHR))
forall a b. (a -> b) -> a -> b
$ Ptr AccelerationStructureGeometryKHR
-> (Ptr (Ptr AccelerationStructureGeometryKHR) -> IO b) -> IO b
forall a b. Storable a => a -> (Ptr a -> IO b) -> IO b
with (Ptr AccelerationStructureGeometryKHR
pPpGeometries')
    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 AccelerationStructureGeometryKHR))
-> Ptr (Ptr AccelerationStructureGeometryKHR) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr (Ptr (Ptr AccelerationStructureGeometryKHR))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr (Ptr AccelerationStructureGeometryKHR)))) Ptr (Ptr AccelerationStructureGeometryKHR)
ppGeometries''
    ((() -> 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 ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr DeviceOrHostAddressKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: 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 -> 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 = 72
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (AccelerationStructureBuildGeometryInfoKHR es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p f :: 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 (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_BUILD_GEOMETRY_INFO_KHR)
    "data" ::: Ptr ()
pNext' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    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 (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext'
    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 AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr AccelerationStructureTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureTypeKHR)) (AccelerationStructureTypeKHR
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 Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
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 ((Ptr (AccelerationStructureBuildGeometryInfoKHR es)
p Ptr (AccelerationStructureBuildGeometryInfoKHR es)
-> Int -> Ptr DeviceOrHostAddressKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: 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 -> 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 es ~ '[] => Zero (AccelerationStructureBuildGeometryInfoKHR es) where
  zero :: AccelerationStructureBuildGeometryInfoKHR es
zero = Chain es
-> AccelerationStructureTypeKHR
-> BuildAccelerationStructureFlagsKHR
-> Bool
-> AccelerationStructureKHR
-> AccelerationStructureKHR
-> Vector AccelerationStructureGeometryKHR
-> DeviceOrHostAddressKHR
-> AccelerationStructureBuildGeometryInfoKHR es
forall (es :: [*]).
Chain es
-> AccelerationStructureTypeKHR
-> BuildAccelerationStructureFlagsKHR
-> Bool
-> AccelerationStructureKHR
-> AccelerationStructureKHR
-> Vector AccelerationStructureGeometryKHR
-> DeviceOrHostAddressKHR
-> AccelerationStructureBuildGeometryInfoKHR es
AccelerationStructureBuildGeometryInfoKHR
           ()
           AccelerationStructureTypeKHR
forall a. Zero a => a
zero
           BuildAccelerationStructureFlagsKHR
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero
           AccelerationStructureKHR
forall a. Zero a => a
zero
           AccelerationStructureKHR
forall a. Zero a => a
zero
           Vector AccelerationStructureGeometryKHR
forall a. Monoid a => a
mempty
           DeviceOrHostAddressKHR
forall a. Zero a => a
zero


-- | VkAccelerationStructureBuildOffsetInfoKHR - Structure specifying build
-- offsets and counts for acceleration structure builds
--
-- = Description
--
-- The primitive count and primitive offset are interpreted differently
-- depending on the 'GeometryTypeKHR' used:
--
-- -   For geometries of type 'GEOMETRY_TYPE_TRIANGLES_KHR',
--     @primitiveCount@ is the number of triangles to be built, where each
--     triangle is treated as 3 vertices.
--
--     -   If the geometry uses indices, @primitiveCount@ × 3 indices are
--         consumed from
--         'AccelerationStructureGeometryTrianglesDataKHR'::@indexData@,
--         starting at an offset of @primitiveOffset@. The value of
--         @firstVertex@ is added to the index values before fetching
--         vertices.
--
--     -   If the geometry does not use indices, @primitiveCount@ × 3
--         vertices are consumed from
--         'AccelerationStructureGeometryTrianglesDataKHR'::@vertexData@,
--         starting at an offset of @primitiveOffset@ +
--         'AccelerationStructureGeometryTrianglesDataKHR'::@vertexStride@
--         × @firstVertex@.
--
--     -   A single 'TransformMatrixKHR' structure is consumed from
--         'AccelerationStructureGeometryTrianglesDataKHR'::@transformData@,
--         at an offset of @transformOffset@. This transformation matrix is
--         used by all triangles.
--
-- -   For geometries of type 'GEOMETRY_TYPE_AABBS_KHR', @primitiveCount@
--     is the number of axis-aligned bounding boxes. @primitiveCount@
--     'AabbPositionsKHR' structures are consumed from
--     'AccelerationStructureGeometryAabbsDataKHR'::@data@, starting at an
--     offset of @primitiveOffset@.
--
-- -   For geometries of type 'GEOMETRY_TYPE_INSTANCES_KHR',
--     @primitiveCount@ is the number of acceleration structures.
--     @primitiveCount@ 'AccelerationStructureInstanceKHR' structures are
--     consumed from
--     'AccelerationStructureGeometryInstancesDataKHR'::@data@, starting at
--     an offset of @primitiveOffset@.
--
-- == Valid Usage
--
-- -   For geometries of type 'GEOMETRY_TYPE_TRIANGLES_KHR', if the
--     geometry uses indices, the offset @primitiveOffset@ from
--     'AccelerationStructureGeometryTrianglesDataKHR'::@indexData@ /must/
--     be a multiple of the element size of
--     'AccelerationStructureGeometryTrianglesDataKHR'::@indexType@
--
-- -   For geometries of type 'GEOMETRY_TYPE_TRIANGLES_KHR', if the
--     geometry doesn’t use indices, the offset @primitiveOffset@ from
--     'AccelerationStructureGeometryTrianglesDataKHR'::@vertexData@ /must/
--     be a multiple of the component size of
--     'AccelerationStructureGeometryTrianglesDataKHR'::@vertexFormat@
--
-- -   For geometries of type 'GEOMETRY_TYPE_TRIANGLES_KHR', the offset
--     @transformOffset@ from
--     'AccelerationStructureGeometryTrianglesDataKHR'::@transformData@
--     /must/ be a multiple of 16
--
-- -   For geometries of type 'GEOMETRY_TYPE_AABBS_KHR', the offset
--     @primitiveOffset@ from
--     'AccelerationStructureGeometryAabbsDataKHR'::@data@ /must/ be a
--     multiple of 8
--
-- -   For geometries of type 'GEOMETRY_TYPE_INSTANCES_KHR', the offset
--     @primitiveOffset@ from
--     'AccelerationStructureGeometryInstancesDataKHR'::@data@ /must/ be a
--     multiple of 16 \/\/ TODO - Almost certainly should be more here
--
-- = See Also
--
-- 'buildAccelerationStructureKHR', 'cmdBuildAccelerationStructureKHR'
data AccelerationStructureBuildOffsetInfoKHR = AccelerationStructureBuildOffsetInfoKHR
  { -- | @primitiveCount@ defines the number of primitives for a corresponding
    -- acceleration structure geometry.
    AccelerationStructureBuildOffsetInfoKHR
-> "bindInfoCount" ::: Word32
primitiveCount :: Word32
  , -- | @primitiveOffset@ defines an offset in bytes into the memory where
    -- primitive data is defined.
    AccelerationStructureBuildOffsetInfoKHR
-> "bindInfoCount" ::: Word32
primitiveOffset :: Word32
  , -- | @firstVertex@ is the index of the first vertex to build from for
    -- triangle geometry.
    AccelerationStructureBuildOffsetInfoKHR
-> "bindInfoCount" ::: Word32
firstVertex :: Word32
  , -- | @transformOffset@ defines an offset in bytes into the memory where a
    -- transform matrix is defined.
    AccelerationStructureBuildOffsetInfoKHR
-> "bindInfoCount" ::: Word32
transformOffset :: Word32
  }
  deriving (Typeable, AccelerationStructureBuildOffsetInfoKHR
-> AccelerationStructureBuildOffsetInfoKHR -> Bool
(AccelerationStructureBuildOffsetInfoKHR
 -> AccelerationStructureBuildOffsetInfoKHR -> Bool)
-> (AccelerationStructureBuildOffsetInfoKHR
    -> AccelerationStructureBuildOffsetInfoKHR -> Bool)
-> Eq AccelerationStructureBuildOffsetInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureBuildOffsetInfoKHR
-> AccelerationStructureBuildOffsetInfoKHR -> Bool
$c/= :: AccelerationStructureBuildOffsetInfoKHR
-> AccelerationStructureBuildOffsetInfoKHR -> Bool
== :: AccelerationStructureBuildOffsetInfoKHR
-> AccelerationStructureBuildOffsetInfoKHR -> Bool
$c== :: AccelerationStructureBuildOffsetInfoKHR
-> AccelerationStructureBuildOffsetInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureBuildOffsetInfoKHR)
#endif
deriving instance Show AccelerationStructureBuildOffsetInfoKHR

instance ToCStruct AccelerationStructureBuildOffsetInfoKHR where
  withCStruct :: AccelerationStructureBuildOffsetInfoKHR
-> (Ptr AccelerationStructureBuildOffsetInfoKHR -> IO b) -> IO b
withCStruct x :: AccelerationStructureBuildOffsetInfoKHR
x f :: Ptr AccelerationStructureBuildOffsetInfoKHR -> IO b
f = Int
-> Int
-> (Ptr AccelerationStructureBuildOffsetInfoKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 4 ((Ptr AccelerationStructureBuildOffsetInfoKHR -> IO b) -> IO b)
-> (Ptr AccelerationStructureBuildOffsetInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AccelerationStructureBuildOffsetInfoKHR
p -> Ptr AccelerationStructureBuildOffsetInfoKHR
-> AccelerationStructureBuildOffsetInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureBuildOffsetInfoKHR
p AccelerationStructureBuildOffsetInfoKHR
x (Ptr AccelerationStructureBuildOffsetInfoKHR -> IO b
f Ptr AccelerationStructureBuildOffsetInfoKHR
p)
  pokeCStruct :: Ptr AccelerationStructureBuildOffsetInfoKHR
-> AccelerationStructureBuildOffsetInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr AccelerationStructureBuildOffsetInfoKHR
p AccelerationStructureBuildOffsetInfoKHR{..} f :: IO b
f = do
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("bindInfoCount" ::: Word32
primitiveCount)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("bindInfoCount" ::: Word32
primitiveOffset)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("bindInfoCount" ::: Word32
firstVertex)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32)) ("bindInfoCount" ::: Word32
transformOffset)
    IO b
f
  cStructSize :: Int
cStructSize = 16
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr AccelerationStructureBuildOffsetInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AccelerationStructureBuildOffsetInfoKHR
p f :: IO b
f = do
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct AccelerationStructureBuildOffsetInfoKHR where
  peekCStruct :: Ptr AccelerationStructureBuildOffsetInfoKHR
-> IO AccelerationStructureBuildOffsetInfoKHR
peekCStruct p :: Ptr AccelerationStructureBuildOffsetInfoKHR
p = do
    "bindInfoCount" ::: Word32
primitiveCount <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
    "bindInfoCount" ::: Word32
primitiveOffset <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
    "bindInfoCount" ::: Word32
firstVertex <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
    "bindInfoCount" ::: Word32
transformOffset <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AccelerationStructureBuildOffsetInfoKHR
p Ptr AccelerationStructureBuildOffsetInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr Word32))
    AccelerationStructureBuildOffsetInfoKHR
-> IO AccelerationStructureBuildOffsetInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AccelerationStructureBuildOffsetInfoKHR
 -> IO AccelerationStructureBuildOffsetInfoKHR)
-> AccelerationStructureBuildOffsetInfoKHR
-> IO AccelerationStructureBuildOffsetInfoKHR
forall a b. (a -> b) -> a -> b
$ ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> AccelerationStructureBuildOffsetInfoKHR
AccelerationStructureBuildOffsetInfoKHR
             "bindInfoCount" ::: Word32
primitiveCount "bindInfoCount" ::: Word32
primitiveOffset "bindInfoCount" ::: Word32
firstVertex "bindInfoCount" ::: Word32
transformOffset

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

instance Zero AccelerationStructureBuildOffsetInfoKHR where
  zero :: AccelerationStructureBuildOffsetInfoKHR
zero = ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> AccelerationStructureBuildOffsetInfoKHR
AccelerationStructureBuildOffsetInfoKHR
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero


-- | VkAccelerationStructureCreateGeometryTypeInfoKHR - Structure specifying
-- the shape of geometries that will be built into an acceleration
-- structure
--
-- = Description
--
-- When @geometryType@ is 'GEOMETRY_TYPE_TRIANGLES_KHR':
--
-- -   if @indexType@ is
--     'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_NONE_KHR', then this
--     structure describes a set of triangles.
--
-- -   if @indexType@ is not
--     'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_NONE_KHR', then this
--     structure describes a set of indexed triangles.
--
-- == Valid Usage
--
-- -   If @geometryType@ is 'GEOMETRY_TYPE_TRIANGLES_KHR', @vertexFormat@
--     /must/ support the
--     'Vulkan.Core10.Enums.FormatFeatureFlagBits.FORMAT_FEATURE_ACCELERATION_STRUCTURE_VERTEX_BUFFER_BIT_KHR'
--     in
--     'Vulkan.Core10.DeviceInitialization.FormatProperties'::@bufferFeatures@
--     as returned by
--     'Vulkan.Core11.Promoted_From_VK_KHR_get_physical_device_properties2.getPhysicalDeviceFormatProperties2'
--
-- -   If @geometryType@ is 'GEOMETRY_TYPE_TRIANGLES_KHR', @indexType@
--     /must/ be 'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT16',
--     'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_UINT32', or
--     'Vulkan.Core10.Enums.IndexType.INDEX_TYPE_NONE_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_GEOMETRY_TYPE_INFO_KHR'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @geometryType@ /must/ be a valid 'GeometryTypeKHR' value
--
-- -   @indexType@ /must/ be a valid
--     'Vulkan.Core10.Enums.IndexType.IndexType' value
--
-- -   If @vertexFormat@ is not @0@, @vertexFormat@ /must/ be a valid
--     'Vulkan.Core10.Enums.Format.Format' value
--
-- = See Also
--
-- 'AccelerationStructureCreateInfoKHR',
-- 'Vulkan.Core10.FundamentalTypes.Bool32',
-- 'Vulkan.Core10.Enums.Format.Format', 'GeometryTypeKHR',
-- 'Vulkan.Core10.Enums.IndexType.IndexType',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data AccelerationStructureCreateGeometryTypeInfoKHR = AccelerationStructureCreateGeometryTypeInfoKHR
  { -- | @geometryType@ is a 'GeometryTypeKHR' that describes the type of an
    -- acceleration structure geometry.
    AccelerationStructureCreateGeometryTypeInfoKHR -> GeometryTypeKHR
geometryType :: GeometryTypeKHR
  , -- | @maxPrimitiveCount@ describes the maximum number of primitives that
    -- /can/ be built into an acceleration structure geometry.
    AccelerationStructureCreateGeometryTypeInfoKHR
-> "bindInfoCount" ::: Word32
maxPrimitiveCount :: Word32
  , -- | @indexType@ is a 'Vulkan.Core10.Enums.IndexType.IndexType' that
    -- describes the index type used to build this geometry when @geometryType@
    -- is 'GEOMETRY_TYPE_TRIANGLES_KHR'.
    AccelerationStructureCreateGeometryTypeInfoKHR -> IndexType
indexType :: IndexType
  , -- | @maxVertexCount@ describes the maximum vertex count that /can/ be used
    -- to build an acceleration structure geometry when @geometryType@ is
    -- 'GEOMETRY_TYPE_TRIANGLES_KHR'.
    AccelerationStructureCreateGeometryTypeInfoKHR
-> "bindInfoCount" ::: Word32
maxVertexCount :: Word32
  , -- | @vertexFormat@ is a 'Vulkan.Core10.Enums.Format.Format' that describes
    -- the vertex format used to build this geometry when @geometryType@ is
    -- 'GEOMETRY_TYPE_TRIANGLES_KHR'.
    AccelerationStructureCreateGeometryTypeInfoKHR -> Format
vertexFormat :: Format
  , -- | @allowsTransforms@ indicates whether transform data /can/ be used by
    -- this acceleration structure or not, when @geometryType@ is
    -- 'GEOMETRY_TYPE_TRIANGLES_KHR'.
    AccelerationStructureCreateGeometryTypeInfoKHR -> Bool
allowsTransforms :: Bool
  }
  deriving (Typeable, AccelerationStructureCreateGeometryTypeInfoKHR
-> AccelerationStructureCreateGeometryTypeInfoKHR -> Bool
(AccelerationStructureCreateGeometryTypeInfoKHR
 -> AccelerationStructureCreateGeometryTypeInfoKHR -> Bool)
-> (AccelerationStructureCreateGeometryTypeInfoKHR
    -> AccelerationStructureCreateGeometryTypeInfoKHR -> Bool)
-> Eq AccelerationStructureCreateGeometryTypeInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureCreateGeometryTypeInfoKHR
-> AccelerationStructureCreateGeometryTypeInfoKHR -> Bool
$c/= :: AccelerationStructureCreateGeometryTypeInfoKHR
-> AccelerationStructureCreateGeometryTypeInfoKHR -> Bool
== :: AccelerationStructureCreateGeometryTypeInfoKHR
-> AccelerationStructureCreateGeometryTypeInfoKHR -> Bool
$c== :: AccelerationStructureCreateGeometryTypeInfoKHR
-> AccelerationStructureCreateGeometryTypeInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureCreateGeometryTypeInfoKHR)
#endif
deriving instance Show AccelerationStructureCreateGeometryTypeInfoKHR

instance ToCStruct AccelerationStructureCreateGeometryTypeInfoKHR where
  withCStruct :: AccelerationStructureCreateGeometryTypeInfoKHR
-> (Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
-> IO b
withCStruct x :: AccelerationStructureCreateGeometryTypeInfoKHR
x f :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b
f = Int
-> Int
-> (Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
 -> IO b)
-> (Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p -> Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> AccelerationStructureCreateGeometryTypeInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p AccelerationStructureCreateGeometryTypeInfoKHR
x (Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b
f Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p)
  pokeCStruct :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> AccelerationStructureCreateGeometryTypeInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p AccelerationStructureCreateGeometryTypeInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_GEOMETRY_TYPE_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr GeometryTypeKHR -> GeometryTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr GeometryTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr GeometryTypeKHR)) (GeometryTypeKHR
geometryType)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("bindInfoCount" ::: Word32
maxPrimitiveCount)
    Ptr IndexType -> IndexType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr IndexType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr IndexType)) (IndexType
indexType)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32)) ("bindInfoCount" ::: Word32
maxVertexCount)
    Ptr Format -> Format -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Format)) (Format
vertexFormat)
    Ptr Bool32 -> Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32)) (Bool -> Bool32
boolToBool32 (Bool
allowsTransforms))
    IO b
f
  cStructSize :: Int
cStructSize = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_GEOMETRY_TYPE_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr GeometryTypeKHR -> GeometryTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr GeometryTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr GeometryTypeKHR)) (GeometryTypeKHR
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr IndexType -> IndexType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr IndexType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr IndexType)) (IndexType
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct AccelerationStructureCreateGeometryTypeInfoKHR where
  peekCStruct :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> IO AccelerationStructureCreateGeometryTypeInfoKHR
peekCStruct p :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p = do
    GeometryTypeKHR
geometryType <- Ptr GeometryTypeKHR -> IO GeometryTypeKHR
forall a. Storable a => Ptr a -> IO a
peek @GeometryTypeKHR ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr GeometryTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr GeometryTypeKHR))
    "bindInfoCount" ::: Word32
maxPrimitiveCount <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    IndexType
indexType <- Ptr IndexType -> IO IndexType
forall a. Storable a => Ptr a -> IO a
peek @IndexType ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr IndexType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr IndexType))
    "bindInfoCount" ::: Word32
maxVertexCount <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr Word32))
    Format
vertexFormat <- Ptr Format -> IO Format
forall a. Storable a => Ptr a -> IO a
peek @Format ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr Format
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Format))
    Bool32
allowsTransforms <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
p Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr Bool32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36 :: Ptr Bool32))
    AccelerationStructureCreateGeometryTypeInfoKHR
-> IO AccelerationStructureCreateGeometryTypeInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AccelerationStructureCreateGeometryTypeInfoKHR
 -> IO AccelerationStructureCreateGeometryTypeInfoKHR)
-> AccelerationStructureCreateGeometryTypeInfoKHR
-> IO AccelerationStructureCreateGeometryTypeInfoKHR
forall a b. (a -> b) -> a -> b
$ GeometryTypeKHR
-> ("bindInfoCount" ::: Word32)
-> IndexType
-> ("bindInfoCount" ::: Word32)
-> Format
-> Bool
-> AccelerationStructureCreateGeometryTypeInfoKHR
AccelerationStructureCreateGeometryTypeInfoKHR
             GeometryTypeKHR
geometryType "bindInfoCount" ::: Word32
maxPrimitiveCount IndexType
indexType "bindInfoCount" ::: Word32
maxVertexCount Format
vertexFormat (Bool32 -> Bool
bool32ToBool Bool32
allowsTransforms)

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

instance Zero AccelerationStructureCreateGeometryTypeInfoKHR where
  zero :: AccelerationStructureCreateGeometryTypeInfoKHR
zero = GeometryTypeKHR
-> ("bindInfoCount" ::: Word32)
-> IndexType
-> ("bindInfoCount" ::: Word32)
-> Format
-> Bool
-> AccelerationStructureCreateGeometryTypeInfoKHR
AccelerationStructureCreateGeometryTypeInfoKHR
           GeometryTypeKHR
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           IndexType
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           Format
forall a. Zero a => a
zero
           Bool
forall a. Zero a => a
zero


-- | VkAccelerationStructureCreateInfoKHR - Structure specifying the
-- parameters of a newly created acceleration structure 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 acceleration structure on the same
-- implementation. The acceleration structure /must/ also be bound to an
-- identically created 'Vulkan.Core10.Handles.DeviceMemory' object.
--
-- Apps /should/ avoid creating acceleration structures with app-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.
--
-- == Valid Usage
--
-- -   If @compactedSize@ is not @0@ then @maxGeometryCount@ /must/ be @0@
--
-- -   If @compactedSize@ is @0@ then @maxGeometryCount@ /must/ not be @0@
--
-- -   If @type@ is 'ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR' then
--     @maxGeometryCount@ /must/ be less than or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxGeometryCount@
--
-- -   If @type@ is 'ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR' then the
--     @maxPrimitiveCount@ member of each element of the @pGeometryInfos@
--     array /must/ be less than or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxInstanceCount@
--
-- -   The total number of triangles in all geometries /must/ be less than
--     or equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxPrimitiveCount@
--
-- -   The total number of AABBs in all geometries /must/ be less than or
--     equal to
--     'PhysicalDeviceRayTracingPropertiesKHR'::@maxPrimitiveCount@
--
-- -   If @type@ is 'ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR' and
--     @compactedSize@ is @0@, @maxGeometryCount@ /must/ be @1@
--
-- -   If @type@ is 'ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR' and
--     @compactedSize@ is @0@, the @geometryType@ member of elements of
--     @pGeometryInfos@ /must/ be 'GEOMETRY_TYPE_INSTANCES_KHR'
--
-- -   If @type@ is 'ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR' and
--     @compactedSize@ is @0@, the @geometryType@ member of elements of
--     @pGeometryInfos@ /must/ not be 'GEOMETRY_TYPE_INSTANCES_KHR'
--
-- -   If @type@ is 'ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR' then the
--     @geometryType@ member of each geometry in @pGeometryInfos@ /must/ be
--     the same
--
-- -   If @flags@ has the
--     'BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR' bit set,
--     then it /must/ not have the
--     'BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR' bit set
--
-- -   If @deviceAddress@ is not @0@,
--     'PhysicalDeviceRayTracingFeaturesKHR'::@rayTracingAccelerationStructureCaptureReplay@
--     /must/ be 'Vulkan.Core10.FundamentalTypes.TRUE'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_INFO_KHR'
--
-- -   @pNext@ /must/ be @NULL@
--
-- -   @type@ /must/ be a valid 'AccelerationStructureTypeKHR' value
--
-- -   @flags@ /must/ be a valid combination of
--     'BuildAccelerationStructureFlagBitsKHR' values
--
-- -   If @maxGeometryCount@ is not @0@, @pGeometryInfos@ /must/ be a valid
--     pointer to an array of @maxGeometryCount@ valid
--     'AccelerationStructureCreateGeometryTypeInfoKHR' structures
--
-- = See Also
--
-- 'AccelerationStructureCreateGeometryTypeInfoKHR',
-- 'AccelerationStructureTypeKHR', 'BuildAccelerationStructureFlagsKHR',
-- 'Vulkan.Core10.FundamentalTypes.DeviceAddress',
-- 'Vulkan.Core10.FundamentalTypes.DeviceSize',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'createAccelerationStructureKHR'
data AccelerationStructureCreateInfoKHR = AccelerationStructureCreateInfoKHR
  { -- | @compactedSize@ is the size from the result of
    -- 'cmdWriteAccelerationStructuresPropertiesKHR' if this acceleration
    -- structure is going to be the target of a compacting copy.
    AccelerationStructureCreateInfoKHR -> "dataSize" ::: Word64
compactedSize :: DeviceSize
  , -- | @type@ is a 'AccelerationStructureTypeKHR' value specifying the type of
    -- acceleration structure that will be created.
    AccelerationStructureCreateInfoKHR -> AccelerationStructureTypeKHR
type' :: AccelerationStructureTypeKHR
  , -- | @flags@ is a bitmask of 'BuildAccelerationStructureFlagBitsKHR'
    -- specifying additional parameters of the acceleration structure.
    AccelerationStructureCreateInfoKHR
-> BuildAccelerationStructureFlagsKHR
flags :: BuildAccelerationStructureFlagsKHR
  , -- | @pGeometryInfos@ is an array of @maxGeometryCount@
    -- 'AccelerationStructureCreateGeometryTypeInfoKHR' structures, which
    -- describe the maximum size and format of the data that will be built into
    -- the acceleration structure.
    AccelerationStructureCreateInfoKHR
-> Vector AccelerationStructureCreateGeometryTypeInfoKHR
geometryInfos :: Vector AccelerationStructureCreateGeometryTypeInfoKHR
  , -- | @deviceAddress@ is the device address requested for the acceleration
    -- structure if the
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-raytracing-ascapturereplay rayTracingAccelerationStructureCaptureReplay>
    -- feature is being used.
    AccelerationStructureCreateInfoKHR -> "dataSize" ::: Word64
deviceAddress :: DeviceAddress
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureCreateInfoKHR)
#endif
deriving instance Show AccelerationStructureCreateInfoKHR

instance ToCStruct AccelerationStructureCreateInfoKHR where
  withCStruct :: AccelerationStructureCreateInfoKHR
-> (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
    -> IO b)
-> IO b
withCStruct x :: AccelerationStructureCreateInfoKHR
x f :: ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR) -> IO b
f = Int
-> Int
-> (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 56 8 ((("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
  -> IO b)
 -> IO b)
-> (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p -> ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> AccelerationStructureCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p AccelerationStructureCreateInfoKHR
x (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR) -> IO b
f "pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p)
  pokeCStruct :: ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> AccelerationStructureCreateInfoKHR -> IO b -> IO b
pokeCStruct p :: "pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p AccelerationStructureCreateInfoKHR{..} f :: 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 (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_INFO_KHR)
    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 (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("dataSize" ::: Word64
compactedSize)
    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 AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr AccelerationStructureTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureTypeKHR)) (AccelerationStructureTypeKHR
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 BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr BuildAccelerationStructureFlagsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr BuildAccelerationStructureFlagsKHR)) (BuildAccelerationStructureFlagsKHR
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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ((Int -> "bindInfoCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector AccelerationStructureCreateGeometryTypeInfoKHR -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AccelerationStructureCreateGeometryTypeInfoKHR -> Int)
-> Vector AccelerationStructureCreateGeometryTypeInfoKHR -> Int
forall a b. (a -> b) -> a -> b
$ (Vector AccelerationStructureCreateGeometryTypeInfoKHR
geometryInfos)) :: Word32))
    Ptr AccelerationStructureCreateGeometryTypeInfoKHR
pPGeometryInfos' <- ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
 -> IO b)
-> ContT b IO (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
  -> IO b)
 -> ContT b IO (Ptr AccelerationStructureCreateGeometryTypeInfoKHR))
-> ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
    -> IO b)
-> ContT b IO (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AccelerationStructureCreateGeometryTypeInfoKHR ((Vector AccelerationStructureCreateGeometryTypeInfoKHR -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector AccelerationStructureCreateGeometryTypeInfoKHR
geometryInfos)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
    (Int
 -> AccelerationStructureCreateGeometryTypeInfoKHR -> ContT b IO ())
-> Vector AccelerationStructureCreateGeometryTypeInfoKHR
-> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AccelerationStructureCreateGeometryTypeInfoKHR
e -> ((() -> 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 AccelerationStructureCreateGeometryTypeInfoKHR
-> AccelerationStructureCreateGeometryTypeInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AccelerationStructureCreateGeometryTypeInfoKHR
pPGeometryInfos' Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr AccelerationStructureCreateGeometryTypeInfoKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR) (AccelerationStructureCreateGeometryTypeInfoKHR
e) (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
$ ())) (Vector AccelerationStructureCreateGeometryTypeInfoKHR
geometryInfos)
    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 AccelerationStructureCreateGeometryTypeInfoKHR)
-> Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr AccelerationStructureCreateGeometryTypeInfoKHR))) (Ptr AccelerationStructureCreateGeometryTypeInfoKHR
pPGeometryInfos')
    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 (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceAddress)) ("dataSize" ::: Word64
deviceAddress)
    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 = 56
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> IO b -> IO b
pokeZeroCStruct p :: "pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p f :: 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 (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_CREATE_INFO_KHR)
    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 (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: 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 AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr AccelerationStructureTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureTypeKHR)) (AccelerationStructureTypeKHR
forall a. Zero a => a
zero)
    Ptr AccelerationStructureCreateGeometryTypeInfoKHR
pPGeometryInfos' <- ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
 -> IO b)
-> ContT b IO (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
  -> IO b)
 -> ContT b IO (Ptr AccelerationStructureCreateGeometryTypeInfoKHR))
-> ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
    -> IO b)
-> ContT b IO (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AccelerationStructureCreateGeometryTypeInfoKHR ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
    (Int
 -> AccelerationStructureCreateGeometryTypeInfoKHR -> ContT b IO ())
-> Vector AccelerationStructureCreateGeometryTypeInfoKHR
-> ContT b IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AccelerationStructureCreateGeometryTypeInfoKHR
e -> ((() -> 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 AccelerationStructureCreateGeometryTypeInfoKHR
-> AccelerationStructureCreateGeometryTypeInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AccelerationStructureCreateGeometryTypeInfoKHR
pPGeometryInfos' Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr AccelerationStructureCreateGeometryTypeInfoKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR) (AccelerationStructureCreateGeometryTypeInfoKHR
e) (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
$ ())) (Vector AccelerationStructureCreateGeometryTypeInfoKHR
forall a. Monoid a => a
mempty)
    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 AccelerationStructureCreateGeometryTypeInfoKHR)
-> Ptr AccelerationStructureCreateGeometryTypeInfoKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr AccelerationStructureCreateGeometryTypeInfoKHR))) (Ptr AccelerationStructureCreateGeometryTypeInfoKHR
pPGeometryInfos')
    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 FromCStruct AccelerationStructureCreateInfoKHR where
  peekCStruct :: ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> IO AccelerationStructureCreateInfoKHR
peekCStruct p :: "pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p = do
    "dataSize" ::: Word64
compactedSize <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
    AccelerationStructureTypeKHR
type' <- Ptr AccelerationStructureTypeKHR -> IO AccelerationStructureTypeKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureTypeKHR (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr AccelerationStructureTypeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureTypeKHR))
    BuildAccelerationStructureFlagsKHR
flags <- Ptr BuildAccelerationStructureFlagsKHR
-> IO BuildAccelerationStructureFlagsKHR
forall a. Storable a => Ptr a -> IO a
peek @BuildAccelerationStructureFlagsKHR (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr BuildAccelerationStructureFlagsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28 :: Ptr BuildAccelerationStructureFlagsKHR))
    "bindInfoCount" ::: Word32
maxGeometryCount <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
    Ptr AccelerationStructureCreateGeometryTypeInfoKHR
pGeometryInfos <- Ptr (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)
-> IO (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr AccelerationStructureCreateGeometryTypeInfoKHR) (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr AccelerationStructureCreateGeometryTypeInfoKHR)))
    Vector AccelerationStructureCreateGeometryTypeInfoKHR
pGeometryInfos' <- Int
-> (Int -> IO AccelerationStructureCreateGeometryTypeInfoKHR)
-> IO (Vector AccelerationStructureCreateGeometryTypeInfoKHR)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("bindInfoCount" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "bindInfoCount" ::: Word32
maxGeometryCount) (\i :: Int
i -> Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> IO AccelerationStructureCreateGeometryTypeInfoKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AccelerationStructureCreateGeometryTypeInfoKHR ((Ptr AccelerationStructureCreateGeometryTypeInfoKHR
pGeometryInfos Ptr AccelerationStructureCreateGeometryTypeInfoKHR
-> Int -> Ptr AccelerationStructureCreateGeometryTypeInfoKHR
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AccelerationStructureCreateGeometryTypeInfoKHR)))
    "dataSize" ::: Word64
deviceAddress <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceAddress (("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR
p ("pCreateInfo" ::: Ptr AccelerationStructureCreateInfoKHR)
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceAddress))
    AccelerationStructureCreateInfoKHR
-> IO AccelerationStructureCreateInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AccelerationStructureCreateInfoKHR
 -> IO AccelerationStructureCreateInfoKHR)
-> AccelerationStructureCreateInfoKHR
-> IO AccelerationStructureCreateInfoKHR
forall a b. (a -> b) -> a -> b
$ ("dataSize" ::: Word64)
-> AccelerationStructureTypeKHR
-> BuildAccelerationStructureFlagsKHR
-> Vector AccelerationStructureCreateGeometryTypeInfoKHR
-> ("dataSize" ::: Word64)
-> AccelerationStructureCreateInfoKHR
AccelerationStructureCreateInfoKHR
             "dataSize" ::: Word64
compactedSize AccelerationStructureTypeKHR
type' BuildAccelerationStructureFlagsKHR
flags Vector AccelerationStructureCreateGeometryTypeInfoKHR
pGeometryInfos' "dataSize" ::: Word64
deviceAddress

instance Zero AccelerationStructureCreateInfoKHR where
  zero :: AccelerationStructureCreateInfoKHR
zero = ("dataSize" ::: Word64)
-> AccelerationStructureTypeKHR
-> BuildAccelerationStructureFlagsKHR
-> Vector AccelerationStructureCreateGeometryTypeInfoKHR
-> ("dataSize" ::: Word64)
-> AccelerationStructureCreateInfoKHR
AccelerationStructureCreateInfoKHR
           "dataSize" ::: Word64
forall a. Zero a => a
zero
           AccelerationStructureTypeKHR
forall a. Zero a => a
zero
           BuildAccelerationStructureFlagsKHR
forall a. Zero a => a
zero
           Vector AccelerationStructureCreateGeometryTypeInfoKHR
forall a. Monoid a => a
mempty
           "dataSize" ::: Word64
forall a. Zero a => a
zero


-- | VkAabbPositionsKHR - Structure specifying two opposing corners of an
-- axis-aligned bounding box
--
-- == Valid Usage
--
-- = See Also
--
-- No cross-references are available
data AabbPositionsKHR = AabbPositionsKHR
  { -- | @minX@ is the x position of one opposing corner of a bounding box.
    --
    -- @minX@ /must/ be less than or equal to @maxX@
    AabbPositionsKHR -> Float
minX :: Float
  , -- | @minY@ is the y position of one opposing corner of a bounding box.
    --
    -- @minY@ /must/ be less than or equal to @maxY@
    AabbPositionsKHR -> Float
minY :: Float
  , -- | @minZ@ is the z position of one opposing corner of a bounding box.
    --
    -- @minZ@ /must/ be less than or equal to @maxZ@
    AabbPositionsKHR -> Float
minZ :: Float
  , -- | @maxX@ is the x position of the other opposing corner of a bounding box.
    AabbPositionsKHR -> Float
maxX :: Float
  , -- | @maxY@ is the y position of the other opposing corner of a bounding box.
    AabbPositionsKHR -> Float
maxY :: Float
  , -- | @maxZ@ is the z position of the other opposing corner of a bounding box.
    AabbPositionsKHR -> Float
maxZ :: Float
  }
  deriving (Typeable, AabbPositionsKHR -> AabbPositionsKHR -> Bool
(AabbPositionsKHR -> AabbPositionsKHR -> Bool)
-> (AabbPositionsKHR -> AabbPositionsKHR -> Bool)
-> Eq AabbPositionsKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AabbPositionsKHR -> AabbPositionsKHR -> Bool
$c/= :: AabbPositionsKHR -> AabbPositionsKHR -> Bool
== :: AabbPositionsKHR -> AabbPositionsKHR -> Bool
$c== :: AabbPositionsKHR -> AabbPositionsKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AabbPositionsKHR)
#endif
deriving instance Show AabbPositionsKHR

instance ToCStruct AabbPositionsKHR where
  withCStruct :: AabbPositionsKHR -> (Ptr AabbPositionsKHR -> IO b) -> IO b
withCStruct x :: AabbPositionsKHR
x f :: Ptr AabbPositionsKHR -> IO b
f = Int -> Int -> (Ptr AabbPositionsKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 4 ((Ptr AabbPositionsKHR -> IO b) -> IO b)
-> (Ptr AabbPositionsKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AabbPositionsKHR
p -> Ptr AabbPositionsKHR -> AabbPositionsKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AabbPositionsKHR
p AabbPositionsKHR
x (Ptr AabbPositionsKHR -> IO b
f Ptr AabbPositionsKHR
p)
  pokeCStruct :: Ptr AabbPositionsKHR -> AabbPositionsKHR -> IO b -> IO b
pokeCStruct p :: Ptr AabbPositionsKHR
p AabbPositionsKHR{..} f :: IO b
f = do
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
minX))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
minY))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
minZ))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxX))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxY))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
maxZ))
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr AabbPositionsKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AabbPositionsKHR
p f :: IO b
f = do
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr CFloat)) (Float -> CFloat
CFloat (Float
forall a. Zero a => a
zero))
    IO b
f

instance FromCStruct AabbPositionsKHR where
  peekCStruct :: Ptr AabbPositionsKHR -> IO AabbPositionsKHR
peekCStruct p :: Ptr AabbPositionsKHR
p = do
    CFloat
minX <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr CFloat))
    CFloat
minY <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat))
    CFloat
minZ <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat))
    CFloat
maxX <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat))
    CFloat
maxY <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CFloat))
    CFloat
maxZ <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr AabbPositionsKHR
p Ptr AabbPositionsKHR -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr CFloat))
    AabbPositionsKHR -> IO AabbPositionsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AabbPositionsKHR -> IO AabbPositionsKHR)
-> AabbPositionsKHR -> IO AabbPositionsKHR
forall a b. (a -> b) -> a -> b
$ Float
-> Float -> Float -> Float -> Float -> Float -> AabbPositionsKHR
AabbPositionsKHR
             ((\(CFloat a :: Float
a) -> Float
a) CFloat
minX) ((\(CFloat a :: Float
a) -> Float
a) CFloat
minY) ((\(CFloat a :: Float
a) -> Float
a) CFloat
minZ) ((\(CFloat a :: Float
a) -> Float
a) CFloat
maxX) ((\(CFloat a :: Float
a) -> Float
a) CFloat
maxY) ((\(CFloat a :: Float
a) -> Float
a) CFloat
maxZ)

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

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


-- | VkTransformMatrixKHR - Structure specifying a 3x4 affine transformation
-- matrix
--
-- = See Also
--
-- 'AccelerationStructureInstanceKHR'
data TransformMatrixKHR = TransformMatrixKHR
  { -- | @matrix@ is a 3x4 row-major affine transformation matrix.
    TransformMatrixKHR
-> ((Float, Float, Float, Float), (Float, Float, Float, Float),
    (Float, Float, Float, Float))
matrix :: ((Float, Float, Float, Float), (Float, Float, Float, Float), (Float, Float, Float, Float)) }
  deriving (Typeable, TransformMatrixKHR -> TransformMatrixKHR -> Bool
(TransformMatrixKHR -> TransformMatrixKHR -> Bool)
-> (TransformMatrixKHR -> TransformMatrixKHR -> Bool)
-> Eq TransformMatrixKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransformMatrixKHR -> TransformMatrixKHR -> Bool
$c/= :: TransformMatrixKHR -> TransformMatrixKHR -> Bool
== :: TransformMatrixKHR -> TransformMatrixKHR -> Bool
$c== :: TransformMatrixKHR -> TransformMatrixKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (TransformMatrixKHR)
#endif
deriving instance Show TransformMatrixKHR

instance ToCStruct TransformMatrixKHR where
  withCStruct :: TransformMatrixKHR -> (Ptr TransformMatrixKHR -> IO b) -> IO b
withCStruct x :: TransformMatrixKHR
x f :: Ptr TransformMatrixKHR -> IO b
f = Int -> Int -> (Ptr TransformMatrixKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 4 ((Ptr TransformMatrixKHR -> IO b) -> IO b)
-> (Ptr TransformMatrixKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr TransformMatrixKHR
p -> Ptr TransformMatrixKHR -> TransformMatrixKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr TransformMatrixKHR
p TransformMatrixKHR
x (Ptr TransformMatrixKHR -> IO b
f Ptr TransformMatrixKHR
p)
  pokeCStruct :: Ptr TransformMatrixKHR -> TransformMatrixKHR -> IO b -> IO b
pokeCStruct p :: Ptr TransformMatrixKHR
p TransformMatrixKHR{..} f :: IO b
f = do
    let pMatrix' :: Ptr (FixedArray 4 CFloat)
pMatrix' = Ptr (FixedArray 3 (FixedArray 4 CFloat))
-> Ptr (FixedArray 4 CFloat)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr TransformMatrixKHR
p Ptr TransformMatrixKHR
-> Int -> Ptr (FixedArray 3 (FixedArray 4 CFloat))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr (FixedArray 3 (FixedArray 4 CFloat))))
    case (((Float, Float, Float, Float), (Float, Float, Float, Float),
 (Float, Float, Float, Float))
matrix) of
      (e0 :: (Float, Float, Float, Float)
e0, e1 :: (Float, Float, Float, Float)
e1, e2 :: (Float, Float, Float, Float)
e2) -> do
        let pMatrix0 :: Ptr CFloat
pMatrix0 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (Ptr (FixedArray 4 CFloat)
pMatrix' :: Ptr (FixedArray 4 CFloat))
        case ((Float, Float, Float, Float)
e0) of
          (e0' :: Float
e0', e1' :: Float
e1', e2' :: Float
e2', e3 :: Float
e3) -> do
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix0 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
        let pMatrix1 :: Ptr CFloat
pMatrix1 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (Ptr (FixedArray 4 CFloat)
pMatrix' Ptr (FixedArray 4 CFloat) -> Int -> Ptr (FixedArray 4 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray 4 CFloat))
        case ((Float, Float, Float, Float)
e1) of
          (e0' :: Float
e0', e1' :: Float
e1', e2' :: Float
e2', e3 :: Float
e3) -> do
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix1 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
        let pMatrix2 :: Ptr CFloat
pMatrix2 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (Ptr (FixedArray 4 CFloat)
pMatrix' Ptr (FixedArray 4 CFloat) -> Int -> Ptr (FixedArray 4 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (FixedArray 4 CFloat))
        case ((Float, Float, Float, Float)
e2) of
          (e0' :: Float
e0', e1' :: Float
e1', e2' :: Float
e2', e3 :: Float
e3) -> do
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix2 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
        () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
    IO b
f
  cStructSize :: Int
cStructSize = 48
  cStructAlignment :: Int
cStructAlignment = 4
  pokeZeroCStruct :: Ptr TransformMatrixKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr TransformMatrixKHR
p f :: IO b
f = do
    let pMatrix' :: Ptr (FixedArray 4 CFloat)
pMatrix' = Ptr (FixedArray 3 (FixedArray 4 CFloat))
-> Ptr (FixedArray 4 CFloat)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr TransformMatrixKHR
p Ptr TransformMatrixKHR
-> Int -> Ptr (FixedArray 3 (FixedArray 4 CFloat))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr (FixedArray 3 (FixedArray 4 CFloat))))
    case (((Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero), (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero), (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero))) of
      (e0 :: (Float, Float, Float, Float)
e0, e1 :: (Float, Float, Float, Float)
e1, e2 :: (Float, Float, Float, Float)
e2) -> do
        let pMatrix0 :: Ptr CFloat
pMatrix0 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (Ptr (FixedArray 4 CFloat)
pMatrix' :: Ptr (FixedArray 4 CFloat))
        case ((Float, Float, Float, Float)
e0) of
          (e0' :: Float
e0', e1' :: Float
e1', e2' :: Float
e2', e3 :: Float
e3) -> do
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix0 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
        let pMatrix1 :: Ptr CFloat
pMatrix1 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (Ptr (FixedArray 4 CFloat)
pMatrix' Ptr (FixedArray 4 CFloat) -> Int -> Ptr (FixedArray 4 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (FixedArray 4 CFloat))
        case ((Float, Float, Float, Float)
e1) of
          (e0' :: Float
e0', e1' :: Float
e1', e2' :: Float
e2', e3 :: Float
e3) -> do
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix1 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
        let pMatrix2 :: Ptr CFloat
pMatrix2 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr (Ptr (FixedArray 4 CFloat)
pMatrix' Ptr (FixedArray 4 CFloat) -> Int -> Ptr (FixedArray 4 CFloat)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (FixedArray 4 CFloat))
        case ((Float, Float, Float, Float)
e2) of
          (e0' :: Float
e0', e1' :: Float
e1', e2' :: Float
e2', e3 :: Float
e3) -> do
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix2 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e0'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e1'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e2'))
            Ptr CFloat -> CFloat -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr CFloat
pMatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr CFloat) (Float -> CFloat
CFloat (Float
e3))
        () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
    IO b
f

instance FromCStruct TransformMatrixKHR where
  peekCStruct :: Ptr TransformMatrixKHR -> IO TransformMatrixKHR
peekCStruct p :: Ptr TransformMatrixKHR
p = do
    let pmatrix :: Ptr (FixedArray 4 CFloat)
pmatrix = Ptr (FixedArray 3 (FixedArray 4 CFloat))
-> Ptr (FixedArray 4 CFloat)
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @(FixedArray 4 CFloat) ((Ptr TransformMatrixKHR
p Ptr TransformMatrixKHR
-> Int -> Ptr (FixedArray 3 (FixedArray 4 CFloat))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr (FixedArray 3 (FixedArray 4 CFloat))))
    let pmatrix0 :: Ptr CFloat
pmatrix0 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @CFloat ((Ptr (FixedArray 4 CFloat)
pmatrix Ptr (FixedArray 4 CFloat) -> Int -> Ptr (FixedArray 4 CFloat)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr (FixedArray 4 CFloat)))
    CFloat
matrix00 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr CFloat))
    CFloat
matrix01 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr CFloat))
    CFloat
matrix02 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 8 :: Ptr CFloat))
    CFloat
matrix03 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix0 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 12 :: Ptr CFloat))
    let pmatrix1 :: Ptr CFloat
pmatrix1 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @CFloat ((Ptr (FixedArray 4 CFloat)
pmatrix Ptr (FixedArray 4 CFloat) -> Int -> Ptr (FixedArray 4 CFloat)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 16 :: Ptr (FixedArray 4 CFloat)))
    CFloat
matrix10 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr CFloat))
    CFloat
matrix11 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr CFloat))
    CFloat
matrix12 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 8 :: Ptr CFloat))
    CFloat
matrix13 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix1 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 12 :: Ptr CFloat))
    let pmatrix2 :: Ptr CFloat
pmatrix2 = Ptr (FixedArray 4 CFloat) -> Ptr CFloat
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @CFloat ((Ptr (FixedArray 4 CFloat)
pmatrix Ptr (FixedArray 4 CFloat) -> Int -> Ptr (FixedArray 4 CFloat)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 32 :: Ptr (FixedArray 4 CFloat)))
    CFloat
matrix20 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 0 :: Ptr CFloat))
    CFloat
matrix21 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 4 :: Ptr CFloat))
    CFloat
matrix22 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 8 :: Ptr CFloat))
    CFloat
matrix23 <- Ptr CFloat -> IO CFloat
forall a. Storable a => Ptr a -> IO a
peek @CFloat ((Ptr CFloat
pmatrix2 Ptr CFloat -> Int -> Ptr CFloat
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` 12 :: Ptr CFloat))
    TransformMatrixKHR -> IO TransformMatrixKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (TransformMatrixKHR -> IO TransformMatrixKHR)
-> TransformMatrixKHR -> IO TransformMatrixKHR
forall a b. (a -> b) -> a -> b
$ ((Float, Float, Float, Float), (Float, Float, Float, Float),
 (Float, Float, Float, Float))
-> TransformMatrixKHR
TransformMatrixKHR
             ((((((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix00), ((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix01), ((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix02), ((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix03))), ((((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix10), ((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix11), ((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix12), ((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix13))), ((((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix20), ((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix21), ((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix22), ((\(CFloat a :: Float
a) -> Float
a) CFloat
matrix23)))))

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

instance Zero TransformMatrixKHR where
  zero :: TransformMatrixKHR
zero = ((Float, Float, Float, Float), (Float, Float, Float, Float),
 (Float, Float, Float, Float))
-> TransformMatrixKHR
TransformMatrixKHR
           ((Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero), (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero), (Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero, Float
forall a. Zero a => a
zero))


-- | VkAccelerationStructureInstanceKHR - Structure specifying a single
-- acceleration structure instance for building into an acceleration
-- structure geometry
--
-- = Description
--
-- The C language spec does not define the ordering of bit-fields, but in
-- practice, this struct produces the correct layout with existing
-- compilers. The intended bit pattern is for the following:
--
-- If a compiler produces code that diverges from that pattern,
-- applications /must/ employ another method to set values according to the
-- correct bit pattern.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'GeometryInstanceFlagsKHR', 'TransformMatrixKHR'
data AccelerationStructureInstanceKHR = AccelerationStructureInstanceKHR
  { -- | @transform@ is a 'TransformMatrixKHR' structure describing a
    -- transformation to be applied to the acceleration structure.
    AccelerationStructureInstanceKHR -> TransformMatrixKHR
transform :: TransformMatrixKHR
  , -- | @instanceCustomIndex@ is a 24-bit user-specified index value accessible
    -- to ray shaders in the @InstanceCustomIndexKHR@ built-in.
    --
    -- @instanceCustomIndex@ and @mask@ occupy the same memory as if a single
    -- @int32_t@ was specified in their place
    --
    -- -   @instanceCustomIndex@ occupies the 24 least significant bits of that
    --     memory
    --
    -- -   @mask@ occupies the 8 most significant bits of that memory
    AccelerationStructureInstanceKHR -> "bindInfoCount" ::: Word32
instanceCustomIndex :: Word32
  , -- | @mask@ is an 8-bit visibility mask for the geometry. The instance /may/
    -- only be hit if @rayMask & instance.mask != 0@
    AccelerationStructureInstanceKHR -> "bindInfoCount" ::: Word32
mask :: Word32
  , -- | @instanceShaderBindingTableRecordOffset@ is a 24-bit offset used in
    -- calculating the hit shader binding table index.
    --
    -- @instanceShaderBindingTableRecordOffset@ and @flags@ occupy the same
    -- memory as if a single @int32_t@ was specified in their place
    --
    -- -   @instanceShaderBindingTableRecordOffset@ occupies the 24 least
    --     significant bits of that memory
    --
    -- -   @flags@ occupies the 8 most significant bits of that memory
    AccelerationStructureInstanceKHR -> "bindInfoCount" ::: Word32
instanceShaderBindingTableRecordOffset :: Word32
  , -- | @flags@ is an 8-bit mask of 'GeometryInstanceFlagBitsKHR' values to
    -- apply to this instance.
    --
    -- @flags@ /must/ be a valid combination of 'GeometryInstanceFlagBitsKHR'
    -- values
    AccelerationStructureInstanceKHR -> GeometryInstanceFlagsKHR
flags :: GeometryInstanceFlagsKHR
  , -- | @accelerationStructureReference@ is either:
    --
    -- -   a device address containing the value obtained from
    --     'getAccelerationStructureDeviceAddressKHR' or
    --     'Vulkan.Extensions.VK_NV_ray_tracing.getAccelerationStructureHandleNV'
    --     (used by device operations which reference acceleration structures)
    --     or,
    --
    -- -   a 'Vulkan.Extensions.Handles.AccelerationStructureKHR' object (used
    --     by host operations which reference acceleration structures).
    AccelerationStructureInstanceKHR -> "dataSize" ::: Word64
accelerationStructureReference :: Word64
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureInstanceKHR)
#endif
deriving instance Show AccelerationStructureInstanceKHR

instance ToCStruct AccelerationStructureInstanceKHR where
  withCStruct :: AccelerationStructureInstanceKHR
-> (Ptr AccelerationStructureInstanceKHR -> IO b) -> IO b
withCStruct x :: AccelerationStructureInstanceKHR
x f :: Ptr AccelerationStructureInstanceKHR -> IO b
f = Int
-> Int -> (Ptr AccelerationStructureInstanceKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr AccelerationStructureInstanceKHR -> IO b) -> IO b)
-> (Ptr AccelerationStructureInstanceKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AccelerationStructureInstanceKHR
p -> Ptr AccelerationStructureInstanceKHR
-> AccelerationStructureInstanceKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureInstanceKHR
p AccelerationStructureInstanceKHR
x (Ptr AccelerationStructureInstanceKHR -> IO b
f Ptr AccelerationStructureInstanceKHR
p)
  pokeCStruct :: Ptr AccelerationStructureInstanceKHR
-> AccelerationStructureInstanceKHR -> IO b -> IO b
pokeCStruct p :: Ptr AccelerationStructureInstanceKHR
p AccelerationStructureInstanceKHR{..} f :: 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 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 TransformMatrixKHR -> TransformMatrixKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr TransformMatrixKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr TransformMatrixKHR)) (TransformMatrixKHR
transform) (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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) (((("bindInfoCount" ::: Word32) -> "bindInfoCount" ::: Word32
forall a b. Coercible a b => a -> b
coerce @_ @Word32 ("bindInfoCount" ::: Word32
mask)) ("bindInfoCount" ::: Word32) -> Int -> "bindInfoCount" ::: Word32
forall a. Bits a => a -> Int -> a
`shiftL` 24) ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> "bindInfoCount" ::: Word32
forall a. Bits a => a -> a -> a
.|. ("bindInfoCount" ::: Word32
instanceCustomIndex))
    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 ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32)) (((GeometryInstanceFlagsKHR -> "bindInfoCount" ::: Word32
forall a b. Coercible a b => a -> b
coerce @_ @Word32 (GeometryInstanceFlagsKHR
flags)) ("bindInfoCount" ::: Word32) -> Int -> "bindInfoCount" ::: Word32
forall a. Bits a => a -> Int -> a
`shiftL` 24) ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> "bindInfoCount" ::: Word32
forall a. Bits a => a -> a -> a
.|. ("bindInfoCount" ::: Word32
instanceShaderBindingTableRecordOffset))
    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 AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word64)) ("dataSize" ::: Word64
accelerationStructureReference)
    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 = 64
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr AccelerationStructureInstanceKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AccelerationStructureInstanceKHR
p f :: 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 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 TransformMatrixKHR -> TransformMatrixKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr TransformMatrixKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr TransformMatrixKHR)) (TransformMatrixKHR
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 AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word64)) ("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 FromCStruct AccelerationStructureInstanceKHR where
  peekCStruct :: Ptr AccelerationStructureInstanceKHR
-> IO AccelerationStructureInstanceKHR
peekCStruct p :: Ptr AccelerationStructureInstanceKHR
p = do
    TransformMatrixKHR
transform <- Ptr TransformMatrixKHR -> IO TransformMatrixKHR
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @TransformMatrixKHR ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr TransformMatrixKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr TransformMatrixKHR))
    "bindInfoCount" ::: Word32
instanceCustomIndex <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    let instanceCustomIndex' :: "bindInfoCount" ::: Word32
instanceCustomIndex' = (("bindInfoCount" ::: Word32
instanceCustomIndex ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> "bindInfoCount" ::: Word32
forall a. Bits a => a -> a -> a
.&. ("bindInfoCount" ::: Word32) -> "bindInfoCount" ::: Word32
forall a b. Coercible a b => a -> b
coerce @Word32 0xffffff))
    "bindInfoCount" ::: Word32
mask <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
    let mask' :: "bindInfoCount" ::: Word32
mask' = (((("bindInfoCount" ::: Word32
mask ("bindInfoCount" ::: Word32) -> Int -> "bindInfoCount" ::: Word32
forall a. Bits a => a -> Int -> a
`shiftR` 24)) ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> "bindInfoCount" ::: Word32
forall a. Bits a => a -> a -> a
.&. ("bindInfoCount" ::: Word32) -> "bindInfoCount" ::: Word32
forall a b. Coercible a b => a -> b
coerce @Word32 0xff))
    "bindInfoCount" ::: Word32
instanceShaderBindingTableRecordOffset <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr Word32))
    let instanceShaderBindingTableRecordOffset' :: "bindInfoCount" ::: Word32
instanceShaderBindingTableRecordOffset' = (("bindInfoCount" ::: Word32
instanceShaderBindingTableRecordOffset ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> "bindInfoCount" ::: Word32
forall a. Bits a => a -> a -> a
.&. ("bindInfoCount" ::: Word32) -> "bindInfoCount" ::: Word32
forall a b. Coercible a b => a -> b
coerce @Word32 0xffffff))
    GeometryInstanceFlagsKHR
flags <- Ptr GeometryInstanceFlagsKHR -> IO GeometryInstanceFlagsKHR
forall a. Storable a => Ptr a -> IO a
peek @GeometryInstanceFlagsKHR ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr GeometryInstanceFlagsKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 52 :: Ptr GeometryInstanceFlagsKHR))
    let flags' :: GeometryInstanceFlagsKHR
flags' = ((((GeometryInstanceFlagsKHR
flags GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
forall a. Bits a => a -> Int -> a
`shiftR` 24)) GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
forall a. Bits a => a -> a -> a
.&. ("bindInfoCount" ::: Word32) -> GeometryInstanceFlagsKHR
forall a b. Coercible a b => a -> b
coerce @Word32 0xff))
    "dataSize" ::: Word64
accelerationStructureReference <- Ptr ("dataSize" ::: Word64) -> IO ("dataSize" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @Word64 ((Ptr AccelerationStructureInstanceKHR
p Ptr AccelerationStructureInstanceKHR
-> Int -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word64))
    AccelerationStructureInstanceKHR
-> IO AccelerationStructureInstanceKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AccelerationStructureInstanceKHR
 -> IO AccelerationStructureInstanceKHR)
-> AccelerationStructureInstanceKHR
-> IO AccelerationStructureInstanceKHR
forall a b. (a -> b) -> a -> b
$ TransformMatrixKHR
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> GeometryInstanceFlagsKHR
-> ("dataSize" ::: Word64)
-> AccelerationStructureInstanceKHR
AccelerationStructureInstanceKHR
             TransformMatrixKHR
transform "bindInfoCount" ::: Word32
instanceCustomIndex' "bindInfoCount" ::: Word32
mask' "bindInfoCount" ::: Word32
instanceShaderBindingTableRecordOffset' GeometryInstanceFlagsKHR
flags' "dataSize" ::: Word64
accelerationStructureReference

instance Zero AccelerationStructureInstanceKHR where
  zero :: AccelerationStructureInstanceKHR
zero = TransformMatrixKHR
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> GeometryInstanceFlagsKHR
-> ("dataSize" ::: Word64)
-> AccelerationStructureInstanceKHR
AccelerationStructureInstanceKHR
           TransformMatrixKHR
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           GeometryInstanceFlagsKHR
forall a. Zero a => a
zero
           "dataSize" ::: Word64
forall a. Zero a => a
zero


-- | VkAccelerationStructureDeviceAddressInfoKHR - Structure specifying the
-- acceleration structure to query an address for
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getAccelerationStructureDeviceAddressKHR'
data AccelerationStructureDeviceAddressInfoKHR = AccelerationStructureDeviceAddressInfoKHR
  { -- | @accelerationStructure@ specifies the acceleration structure whose
    -- address is being queried.
    --
    -- @accelerationStructure@ /must/ be a valid
    -- 'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
    AccelerationStructureDeviceAddressInfoKHR
-> AccelerationStructureKHR
accelerationStructure :: AccelerationStructureKHR }
  deriving (Typeable, AccelerationStructureDeviceAddressInfoKHR
-> AccelerationStructureDeviceAddressInfoKHR -> Bool
(AccelerationStructureDeviceAddressInfoKHR
 -> AccelerationStructureDeviceAddressInfoKHR -> Bool)
-> (AccelerationStructureDeviceAddressInfoKHR
    -> AccelerationStructureDeviceAddressInfoKHR -> Bool)
-> Eq AccelerationStructureDeviceAddressInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureDeviceAddressInfoKHR
-> AccelerationStructureDeviceAddressInfoKHR -> Bool
$c/= :: AccelerationStructureDeviceAddressInfoKHR
-> AccelerationStructureDeviceAddressInfoKHR -> Bool
== :: AccelerationStructureDeviceAddressInfoKHR
-> AccelerationStructureDeviceAddressInfoKHR -> Bool
$c== :: AccelerationStructureDeviceAddressInfoKHR
-> AccelerationStructureDeviceAddressInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureDeviceAddressInfoKHR)
#endif
deriving instance Show AccelerationStructureDeviceAddressInfoKHR

instance ToCStruct AccelerationStructureDeviceAddressInfoKHR where
  withCStruct :: AccelerationStructureDeviceAddressInfoKHR
-> (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
    -> IO b)
-> IO b
withCStruct x :: AccelerationStructureDeviceAddressInfoKHR
x f :: ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR) -> IO b
f = Int
-> Int
-> (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
    -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
  -> IO b)
 -> IO b)
-> (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
    -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p -> ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> AccelerationStructureDeviceAddressInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p AccelerationStructureDeviceAddressInfoKHR
x (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR) -> IO b
f "pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p)
  pokeCStruct :: ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> AccelerationStructureDeviceAddressInfoKHR -> IO b -> IO b
pokeCStruct p :: "pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p AccelerationStructureDeviceAddressInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_DEVICE_ADDRESS_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
accelerationStructure)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> IO b -> IO b
pokeZeroCStruct p :: "pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_DEVICE_ADDRESS_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct AccelerationStructureDeviceAddressInfoKHR where
  peekCStruct :: ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> IO AccelerationStructureDeviceAddressInfoKHR
peekCStruct p :: "pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p = do
    AccelerationStructureKHR
accelerationStructure <- ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureKHR (("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR
p ("pInfo" ::: Ptr AccelerationStructureDeviceAddressInfoKHR)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR))
    AccelerationStructureDeviceAddressInfoKHR
-> IO AccelerationStructureDeviceAddressInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AccelerationStructureDeviceAddressInfoKHR
 -> IO AccelerationStructureDeviceAddressInfoKHR)
-> AccelerationStructureDeviceAddressInfoKHR
-> IO AccelerationStructureDeviceAddressInfoKHR
forall a b. (a -> b) -> a -> b
$ AccelerationStructureKHR
-> AccelerationStructureDeviceAddressInfoKHR
AccelerationStructureDeviceAddressInfoKHR
             AccelerationStructureKHR
accelerationStructure

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

instance Zero AccelerationStructureDeviceAddressInfoKHR where
  zero :: AccelerationStructureDeviceAddressInfoKHR
zero = AccelerationStructureKHR
-> AccelerationStructureDeviceAddressInfoKHR
AccelerationStructureDeviceAddressInfoKHR
           AccelerationStructureKHR
forall a. Zero a => a
zero


-- | VkAccelerationStructureVersionKHR - Acceleration structure version
-- information
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'getDeviceAccelerationStructureCompatibilityKHR'
data AccelerationStructureVersionKHR = AccelerationStructureVersionKHR
  { -- | @versionData@ is a pointer to the version header as defined in
    -- 'CopyAccelerationStructureModeKHR'
    --
    -- @versionData@ /must/ be a valid pointer to an array of @2@*VK_UUID_SIZE
    -- @uint8_t@ values
    AccelerationStructureVersionKHR -> ByteString
versionData :: ByteString }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AccelerationStructureVersionKHR)
#endif
deriving instance Show AccelerationStructureVersionKHR

instance ToCStruct AccelerationStructureVersionKHR where
  withCStruct :: AccelerationStructureVersionKHR
-> (Ptr AccelerationStructureVersionKHR -> IO b) -> IO b
withCStruct x :: AccelerationStructureVersionKHR
x f :: Ptr AccelerationStructureVersionKHR -> IO b
f = Int -> Int -> (Ptr AccelerationStructureVersionKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr AccelerationStructureVersionKHR -> IO b) -> IO b)
-> (Ptr AccelerationStructureVersionKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AccelerationStructureVersionKHR
p -> Ptr AccelerationStructureVersionKHR
-> AccelerationStructureVersionKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureVersionKHR
p AccelerationStructureVersionKHR
x (Ptr AccelerationStructureVersionKHR -> IO b
f Ptr AccelerationStructureVersionKHR
p)
  pokeCStruct :: Ptr AccelerationStructureVersionKHR
-> AccelerationStructureVersionKHR -> IO b -> IO b
pokeCStruct p :: Ptr AccelerationStructureVersionKHR
p AccelerationStructureVersionKHR{..} f :: 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 AccelerationStructureVersionKHR
p Ptr AccelerationStructureVersionKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_VERSION_KHR)
    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 AccelerationStructureVersionKHR
p Ptr AccelerationStructureVersionKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
== 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 "" "AccelerationStructureVersionKHR::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 (Ptr CChar -> Ptr Word8
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 AccelerationStructureVersionKHR
p Ptr AccelerationStructureVersionKHR -> Int -> Ptr (Ptr Word8)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr AccelerationStructureVersionKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr AccelerationStructureVersionKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureVersionKHR
p Ptr AccelerationStructureVersionKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_ACCELERATION_STRUCTURE_VERSION_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AccelerationStructureVersionKHR
p Ptr AccelerationStructureVersionKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    IO b
f

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

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


-- | VkCopyAccelerationStructureInfoKHR - Parameters for copying an
-- acceleration structure
--
-- == Valid Usage
--
-- -   @mode@ /must/ be 'COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR' or
--     'COPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR'
--
-- -   @src@ /must/ have been built with
--     'BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR' if @mode@ is
--     'COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_INFO_KHR'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @src@ /must/ be a valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
--
-- -   @dst@ /must/ be a valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
--
-- -   @mode@ /must/ be a valid 'CopyAccelerationStructureModeKHR' value
--
-- -   Both of @dst@, and @src@ /must/ have been created, allocated, or
--     retrieved from the same 'Vulkan.Core10.Handles.Device'
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'CopyAccelerationStructureModeKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdCopyAccelerationStructureKHR', 'copyAccelerationStructureKHR'
data CopyAccelerationStructureInfoKHR (es :: [Type]) = CopyAccelerationStructureInfoKHR
  { -- No documentation found for Nested "VkCopyAccelerationStructureInfoKHR" "pNext"
    CopyAccelerationStructureInfoKHR es -> Chain es
next :: Chain es
  , -- | @src@ is the source acceleration structure for the copy.
    CopyAccelerationStructureInfoKHR es -> AccelerationStructureKHR
src :: AccelerationStructureKHR
  , -- | @dst@ is the target acceleration structure for the copy.
    CopyAccelerationStructureInfoKHR es -> AccelerationStructureKHR
dst :: AccelerationStructureKHR
  , -- | @mode@ is a 'CopyAccelerationStructureModeKHR' value that specifies
    -- additional operations to perform during the copy.
    CopyAccelerationStructureInfoKHR es
-> CopyAccelerationStructureModeKHR
mode :: CopyAccelerationStructureModeKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CopyAccelerationStructureInfoKHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (CopyAccelerationStructureInfoKHR es)

instance Extensible CopyAccelerationStructureInfoKHR where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_INFO_KHR
  setNext :: CopyAccelerationStructureInfoKHR ds
-> Chain es -> CopyAccelerationStructureInfoKHR es
setNext x :: CopyAccelerationStructureInfoKHR ds
x next :: Chain es
next = CopyAccelerationStructureInfoKHR ds
x{$sel:next:CopyAccelerationStructureInfoKHR :: Chain es
next = Chain es
next}
  getNext :: CopyAccelerationStructureInfoKHR es -> Chain es
getNext CopyAccelerationStructureInfoKHR{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends CopyAccelerationStructureInfoKHR e => b) -> Maybe b
  extends :: proxy e
-> (Extends CopyAccelerationStructureInfoKHR e => b) -> Maybe b
extends _ f :: Extends CopyAccelerationStructureInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable DeferredOperationInfoKHR) =>
Maybe (e :~: DeferredOperationInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeferredOperationInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends CopyAccelerationStructureInfoKHR e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss CopyAccelerationStructureInfoKHR es, PokeChain es) => ToCStruct (CopyAccelerationStructureInfoKHR es) where
  withCStruct :: CopyAccelerationStructureInfoKHR es
-> (Ptr (CopyAccelerationStructureInfoKHR es) -> IO b) -> IO b
withCStruct x :: CopyAccelerationStructureInfoKHR es
x f :: Ptr (CopyAccelerationStructureInfoKHR es) -> IO b
f = Int
-> Int
-> (Ptr (CopyAccelerationStructureInfoKHR es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr (CopyAccelerationStructureInfoKHR es) -> IO b) -> IO b)
-> (Ptr (CopyAccelerationStructureInfoKHR es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (CopyAccelerationStructureInfoKHR es)
p -> Ptr (CopyAccelerationStructureInfoKHR es)
-> CopyAccelerationStructureInfoKHR es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (CopyAccelerationStructureInfoKHR es)
p CopyAccelerationStructureInfoKHR es
x (Ptr (CopyAccelerationStructureInfoKHR es) -> IO b
f Ptr (CopyAccelerationStructureInfoKHR es)
p)
  pokeCStruct :: Ptr (CopyAccelerationStructureInfoKHR es)
-> CopyAccelerationStructureInfoKHR es -> IO b -> IO b
pokeCStruct p :: Ptr (CopyAccelerationStructureInfoKHR es)
p CopyAccelerationStructureInfoKHR{..} f :: 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 (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_INFO_KHR)
    "data" ::: Ptr ()
pNext'' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    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 (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext''
    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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
src)
    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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
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 CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int -> Ptr CopyAccelerationStructureModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr CopyAccelerationStructureModeKHR)) (CopyAccelerationStructureModeKHR
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 = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (CopyAccelerationStructureInfoKHR es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (CopyAccelerationStructureInfoKHR es)
p f :: 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 (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_INFO_KHR)
    "data" ::: Ptr ()
pNext' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    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 (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext'
    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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
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 CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int -> Ptr CopyAccelerationStructureModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr CopyAccelerationStructureModeKHR)) (CopyAccelerationStructureModeKHR
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 (Extendss CopyAccelerationStructureInfoKHR es, PeekChain es) => FromCStruct (CopyAccelerationStructureInfoKHR es) where
  peekCStruct :: Ptr (CopyAccelerationStructureInfoKHR es)
-> IO (CopyAccelerationStructureInfoKHR es)
peekCStruct p :: Ptr (CopyAccelerationStructureInfoKHR es)
p = do
    "data" ::: Ptr ()
pNext <- Ptr ("data" ::: Ptr ()) -> IO ("data" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
    Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (("data" ::: Ptr ()) -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr "data" ::: Ptr ()
pNext)
    AccelerationStructureKHR
src <- ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureKHR ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR))
    AccelerationStructureKHR
dst <- ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> IO AccelerationStructureKHR
forall a. Storable a => Ptr a -> IO a
peek @AccelerationStructureKHR ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureKHR))
    CopyAccelerationStructureModeKHR
mode <- Ptr CopyAccelerationStructureModeKHR
-> IO CopyAccelerationStructureModeKHR
forall a. Storable a => Ptr a -> IO a
peek @CopyAccelerationStructureModeKHR ((Ptr (CopyAccelerationStructureInfoKHR es)
p Ptr (CopyAccelerationStructureInfoKHR es)
-> Int -> Ptr CopyAccelerationStructureModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr CopyAccelerationStructureModeKHR))
    CopyAccelerationStructureInfoKHR es
-> IO (CopyAccelerationStructureInfoKHR es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (CopyAccelerationStructureInfoKHR es
 -> IO (CopyAccelerationStructureInfoKHR es))
-> CopyAccelerationStructureInfoKHR es
-> IO (CopyAccelerationStructureInfoKHR es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> AccelerationStructureKHR
-> AccelerationStructureKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureInfoKHR es
forall (es :: [*]).
Chain es
-> AccelerationStructureKHR
-> AccelerationStructureKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureInfoKHR es
CopyAccelerationStructureInfoKHR
             Chain es
next AccelerationStructureKHR
src AccelerationStructureKHR
dst CopyAccelerationStructureModeKHR
mode

instance es ~ '[] => Zero (CopyAccelerationStructureInfoKHR es) where
  zero :: CopyAccelerationStructureInfoKHR es
zero = Chain es
-> AccelerationStructureKHR
-> AccelerationStructureKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureInfoKHR es
forall (es :: [*]).
Chain es
-> AccelerationStructureKHR
-> AccelerationStructureKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureInfoKHR es
CopyAccelerationStructureInfoKHR
           ()
           AccelerationStructureKHR
forall a. Zero a => a
zero
           AccelerationStructureKHR
forall a. Zero a => a
zero
           CopyAccelerationStructureModeKHR
forall a. Zero a => a
zero


-- | VkCopyAccelerationStructureToMemoryInfoKHR - Parameters for serializing
-- an acceleration structure
--
-- == Valid Usage
--
-- -   The memory pointed to by @dst@ /must/ be at least as large as the
--     serialization size of @src@, as reported by
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_ACCELERATION_STRUCTURE_SERIALIZATION_SIZE_KHR'
--
-- -   @mode@ /must/ be 'COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_TO_MEMORY_INFO_KHR'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @src@ /must/ be a valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
--
-- -   @dst@ /must/ be a valid 'DeviceOrHostAddressKHR' union
--
-- -   @mode@ /must/ be a valid 'CopyAccelerationStructureModeKHR' value
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'CopyAccelerationStructureModeKHR', 'DeviceOrHostAddressKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdCopyAccelerationStructureToMemoryKHR',
-- 'copyAccelerationStructureToMemoryKHR'
data CopyAccelerationStructureToMemoryInfoKHR (es :: [Type]) = CopyAccelerationStructureToMemoryInfoKHR
  { -- No documentation found for Nested "VkCopyAccelerationStructureToMemoryInfoKHR" "pNext"
    CopyAccelerationStructureToMemoryInfoKHR es -> Chain es
next :: Chain es
  , -- | @src@ is the source acceleration structure for the copy
    CopyAccelerationStructureToMemoryInfoKHR es
-> AccelerationStructureKHR
src :: AccelerationStructureKHR
  , -- | @dst@ is the device or host address to memory which is the target for
    -- the copy
    CopyAccelerationStructureToMemoryInfoKHR es
-> DeviceOrHostAddressKHR
dst :: DeviceOrHostAddressKHR
  , -- | @mode@ is a 'CopyAccelerationStructureModeKHR' value that specifies
    -- additional operations to perform during the copy.
    CopyAccelerationStructureToMemoryInfoKHR es
-> CopyAccelerationStructureModeKHR
mode :: CopyAccelerationStructureModeKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CopyAccelerationStructureToMemoryInfoKHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (CopyAccelerationStructureToMemoryInfoKHR es)

instance Extensible CopyAccelerationStructureToMemoryInfoKHR where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_TO_MEMORY_INFO_KHR
  setNext :: CopyAccelerationStructureToMemoryInfoKHR ds
-> Chain es -> CopyAccelerationStructureToMemoryInfoKHR es
setNext x :: CopyAccelerationStructureToMemoryInfoKHR ds
x next :: Chain es
next = CopyAccelerationStructureToMemoryInfoKHR ds
x{$sel:next:CopyAccelerationStructureToMemoryInfoKHR :: Chain es
next = Chain es
next}
  getNext :: CopyAccelerationStructureToMemoryInfoKHR es -> Chain es
getNext CopyAccelerationStructureToMemoryInfoKHR{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends CopyAccelerationStructureToMemoryInfoKHR e => b) -> Maybe b
  extends :: proxy e
-> (Extends CopyAccelerationStructureToMemoryInfoKHR e => b)
-> Maybe b
extends _ f :: Extends CopyAccelerationStructureToMemoryInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable DeferredOperationInfoKHR) =>
Maybe (e :~: DeferredOperationInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeferredOperationInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends CopyAccelerationStructureToMemoryInfoKHR e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss CopyAccelerationStructureToMemoryInfoKHR es, PokeChain es) => ToCStruct (CopyAccelerationStructureToMemoryInfoKHR es) where
  withCStruct :: CopyAccelerationStructureToMemoryInfoKHR es
-> (Ptr (CopyAccelerationStructureToMemoryInfoKHR es) -> IO b)
-> IO b
withCStruct x :: CopyAccelerationStructureToMemoryInfoKHR es
x f :: Ptr (CopyAccelerationStructureToMemoryInfoKHR es) -> IO b
f = Int
-> Int
-> (Ptr (CopyAccelerationStructureToMemoryInfoKHR es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr (CopyAccelerationStructureToMemoryInfoKHR es) -> IO b)
 -> IO b)
-> (Ptr (CopyAccelerationStructureToMemoryInfoKHR es) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p -> Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> CopyAccelerationStructureToMemoryInfoKHR es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p CopyAccelerationStructureToMemoryInfoKHR es
x (Ptr (CopyAccelerationStructureToMemoryInfoKHR es) -> IO b
f Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p)
  pokeCStruct :: Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> CopyAccelerationStructureToMemoryInfoKHR es -> IO b -> IO b
pokeCStruct p :: Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p CopyAccelerationStructureToMemoryInfoKHR{..} f :: 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 (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_TO_MEMORY_INFO_KHR)
    "data" ::: Ptr ()
pNext'' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    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 (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext''
    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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
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 ((Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int -> Ptr DeviceOrHostAddressKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int -> Ptr CopyAccelerationStructureModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr CopyAccelerationStructureModeKHR)) (CopyAccelerationStructureModeKHR
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 = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (CopyAccelerationStructureToMemoryInfoKHR es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p f :: 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 (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_ACCELERATION_STRUCTURE_TO_MEMORY_INFO_KHR)
    "data" ::: Ptr ()
pNext' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    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 (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext'
    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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
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 ((Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int -> Ptr DeviceOrHostAddressKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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 CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
p Ptr (CopyAccelerationStructureToMemoryInfoKHR es)
-> Int -> Ptr CopyAccelerationStructureModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr CopyAccelerationStructureModeKHR)) (CopyAccelerationStructureModeKHR
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 es ~ '[] => Zero (CopyAccelerationStructureToMemoryInfoKHR es) where
  zero :: CopyAccelerationStructureToMemoryInfoKHR es
zero = Chain es
-> AccelerationStructureKHR
-> DeviceOrHostAddressKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureToMemoryInfoKHR es
forall (es :: [*]).
Chain es
-> AccelerationStructureKHR
-> DeviceOrHostAddressKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureToMemoryInfoKHR es
CopyAccelerationStructureToMemoryInfoKHR
           ()
           AccelerationStructureKHR
forall a. Zero a => a
zero
           DeviceOrHostAddressKHR
forall a. Zero a => a
zero
           CopyAccelerationStructureModeKHR
forall a. Zero a => a
zero


-- | VkCopyMemoryToAccelerationStructureInfoKHR - Parameters for
-- deserializing an acceleration structure
--
-- == Valid Usage
--
-- -   @mode@ /must/ be 'COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR'
--
-- -   The data in @pInfo->src@ /must/ have a format compatible with the
--     destination physical device as returned by
--     'getDeviceAccelerationStructureCompatibilityKHR'
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_COPY_MEMORY_TO_ACCELERATION_STRUCTURE_INFO_KHR'
--
-- -   @pNext@ /must/ be @NULL@ or a pointer to a valid instance of
--     'Vulkan.Extensions.VK_KHR_deferred_host_operations.DeferredOperationInfoKHR'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   @src@ /must/ be a valid 'DeviceOrHostAddressConstKHR' union
--
-- -   @dst@ /must/ be a valid
--     'Vulkan.Extensions.Handles.AccelerationStructureKHR' handle
--
-- -   @mode@ /must/ be a valid 'CopyAccelerationStructureModeKHR' value
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR',
-- 'CopyAccelerationStructureModeKHR', 'DeviceOrHostAddressConstKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType',
-- 'cmdCopyMemoryToAccelerationStructureKHR',
-- 'copyMemoryToAccelerationStructureKHR'
data CopyMemoryToAccelerationStructureInfoKHR (es :: [Type]) = CopyMemoryToAccelerationStructureInfoKHR
  { -- No documentation found for Nested "VkCopyMemoryToAccelerationStructureInfoKHR" "pNext"
    CopyMemoryToAccelerationStructureInfoKHR es -> Chain es
next :: Chain es
  , -- | @src@ is the device or host address to memory containing the source data
    -- for the copy.
    CopyMemoryToAccelerationStructureInfoKHR es
-> DeviceOrHostAddressConstKHR
src :: DeviceOrHostAddressConstKHR
  , -- | @dst@ is the target acceleration structure for the copy.
    CopyMemoryToAccelerationStructureInfoKHR es
-> AccelerationStructureKHR
dst :: AccelerationStructureKHR
  , -- | @mode@ is a 'CopyAccelerationStructureModeKHR' value that specifies
    -- additional operations to perform during the copy.
    CopyMemoryToAccelerationStructureInfoKHR es
-> CopyAccelerationStructureModeKHR
mode :: CopyAccelerationStructureModeKHR
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (CopyMemoryToAccelerationStructureInfoKHR (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (CopyMemoryToAccelerationStructureInfoKHR es)

instance Extensible CopyMemoryToAccelerationStructureInfoKHR where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_COPY_MEMORY_TO_ACCELERATION_STRUCTURE_INFO_KHR
  setNext :: CopyMemoryToAccelerationStructureInfoKHR ds
-> Chain es -> CopyMemoryToAccelerationStructureInfoKHR es
setNext x :: CopyMemoryToAccelerationStructureInfoKHR ds
x next :: Chain es
next = CopyMemoryToAccelerationStructureInfoKHR ds
x{$sel:next:CopyMemoryToAccelerationStructureInfoKHR :: Chain es
next = Chain es
next}
  getNext :: CopyMemoryToAccelerationStructureInfoKHR es -> Chain es
getNext CopyMemoryToAccelerationStructureInfoKHR{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends CopyMemoryToAccelerationStructureInfoKHR e => b) -> Maybe b
  extends :: proxy e
-> (Extends CopyMemoryToAccelerationStructureInfoKHR e => b)
-> Maybe b
extends _ f :: Extends CopyMemoryToAccelerationStructureInfoKHR e => b
f
    | Just Refl <- (Typeable e, Typeable DeferredOperationInfoKHR) =>
Maybe (e :~: DeferredOperationInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeferredOperationInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends CopyMemoryToAccelerationStructureInfoKHR e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss CopyMemoryToAccelerationStructureInfoKHR es, PokeChain es) => ToCStruct (CopyMemoryToAccelerationStructureInfoKHR es) where
  withCStruct :: CopyMemoryToAccelerationStructureInfoKHR es
-> (Ptr (CopyMemoryToAccelerationStructureInfoKHR es) -> IO b)
-> IO b
withCStruct x :: CopyMemoryToAccelerationStructureInfoKHR es
x f :: Ptr (CopyMemoryToAccelerationStructureInfoKHR es) -> IO b
f = Int
-> Int
-> (Ptr (CopyMemoryToAccelerationStructureInfoKHR es) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr (CopyMemoryToAccelerationStructureInfoKHR es) -> IO b)
 -> IO b)
-> (Ptr (CopyMemoryToAccelerationStructureInfoKHR es) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
p -> Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> CopyMemoryToAccelerationStructureInfoKHR es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
p CopyMemoryToAccelerationStructureInfoKHR es
x (Ptr (CopyMemoryToAccelerationStructureInfoKHR es) -> IO b
f Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
p)
  pokeCStruct :: Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> CopyMemoryToAccelerationStructureInfoKHR es -> IO b -> IO b
pokeCStruct p :: Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
p CopyMemoryToAccelerationStructureInfoKHR{..} f :: 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 (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_MEMORY_TO_ACCELERATION_STRUCTURE_INFO_KHR)
    "data" ::: Ptr ()
pNext'' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
    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 (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext''
    ((() -> 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 (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
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 CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int -> Ptr CopyAccelerationStructureModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr CopyAccelerationStructureModeKHR)) (CopyAccelerationStructureModeKHR
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 = 40
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr (CopyMemoryToAccelerationStructureInfoKHR es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
p f :: 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 (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_COPY_MEMORY_TO_ACCELERATION_STRUCTURE_INFO_KHR)
    "data" ::: Ptr ()
pNext' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
 -> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
    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 (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext'
    ((() -> 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 (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int -> Ptr DeviceOrHostAddressConstKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 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
$ ("pAccelerationStructures" ::: Ptr AccelerationStructureKHR)
-> AccelerationStructureKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int
-> "pAccelerationStructures" ::: Ptr AccelerationStructureKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr AccelerationStructureKHR)) (AccelerationStructureKHR
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 CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
p Ptr (CopyMemoryToAccelerationStructureInfoKHR es)
-> Int -> Ptr CopyAccelerationStructureModeKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr CopyAccelerationStructureModeKHR)) (CopyAccelerationStructureModeKHR
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 es ~ '[] => Zero (CopyMemoryToAccelerationStructureInfoKHR es) where
  zero :: CopyMemoryToAccelerationStructureInfoKHR es
zero = Chain es
-> DeviceOrHostAddressConstKHR
-> AccelerationStructureKHR
-> CopyAccelerationStructureModeKHR
-> CopyMemoryToAccelerationStructureInfoKHR es
forall (es :: [*]).
Chain es
-> DeviceOrHostAddressConstKHR
-> AccelerationStructureKHR
-> CopyAccelerationStructureModeKHR
-> CopyMemoryToAccelerationStructureInfoKHR es
CopyMemoryToAccelerationStructureInfoKHR
           ()
           DeviceOrHostAddressConstKHR
forall a. Zero a => a
zero
           AccelerationStructureKHR
forall a. Zero a => a
zero
           CopyAccelerationStructureModeKHR
forall a. Zero a => a
zero


-- | VkRayTracingPipelineInterfaceCreateInfoKHR - Structure specifying
-- additional interface information when using libraries
--
-- = Description
--
-- @maxPayloadSize@ is calculated as the maximum number of bytes used by
-- any block declared in the @RayPayloadKHR@ or @IncomingRayPayloadKHR@
-- storage classes. @maxAttributeSize@ is calculated as the maximum number
-- of bytes used by any block declared in the @HitAttributeKHR@ storage
-- class. @maxCallableSize@ is calculated as the maximum number of bytes
-- used by any block declred in the @CallableDataKHR@ or
-- @IncomingCallableDataKHR@. As variables in these storage classes do not
-- have explicit offsets, the size should be calculated as if each variable
-- has a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#interfaces-alignment-requirements scalar alignment>
-- equal to the largest scalar alignment of any of the block’s members.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'RayTracingPipelineCreateInfoKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data RayTracingPipelineInterfaceCreateInfoKHR = RayTracingPipelineInterfaceCreateInfoKHR
  { -- | @maxPayloadSize@ is the maximum payload size in bytes used by any shader
    -- in the pipeline.
    RayTracingPipelineInterfaceCreateInfoKHR
-> "bindInfoCount" ::: Word32
maxPayloadSize :: Word32
  , -- | @maxAttributeSize@ is the maximum attribute structure size in bytes used
    -- by any shader in the pipeline.
    RayTracingPipelineInterfaceCreateInfoKHR
-> "bindInfoCount" ::: Word32
maxAttributeSize :: Word32
  , -- | @maxCallableSize@ is the maximum callable data size in bytes used by any
    -- shader in the pipeline.
    RayTracingPipelineInterfaceCreateInfoKHR
-> "bindInfoCount" ::: Word32
maxCallableSize :: Word32
  }
  deriving (Typeable, RayTracingPipelineInterfaceCreateInfoKHR
-> RayTracingPipelineInterfaceCreateInfoKHR -> Bool
(RayTracingPipelineInterfaceCreateInfoKHR
 -> RayTracingPipelineInterfaceCreateInfoKHR -> Bool)
-> (RayTracingPipelineInterfaceCreateInfoKHR
    -> RayTracingPipelineInterfaceCreateInfoKHR -> Bool)
-> Eq RayTracingPipelineInterfaceCreateInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RayTracingPipelineInterfaceCreateInfoKHR
-> RayTracingPipelineInterfaceCreateInfoKHR -> Bool
$c/= :: RayTracingPipelineInterfaceCreateInfoKHR
-> RayTracingPipelineInterfaceCreateInfoKHR -> Bool
== :: RayTracingPipelineInterfaceCreateInfoKHR
-> RayTracingPipelineInterfaceCreateInfoKHR -> Bool
$c== :: RayTracingPipelineInterfaceCreateInfoKHR
-> RayTracingPipelineInterfaceCreateInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RayTracingPipelineInterfaceCreateInfoKHR)
#endif
deriving instance Show RayTracingPipelineInterfaceCreateInfoKHR

instance ToCStruct RayTracingPipelineInterfaceCreateInfoKHR where
  withCStruct :: RayTracingPipelineInterfaceCreateInfoKHR
-> (Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b) -> IO b
withCStruct x :: RayTracingPipelineInterfaceCreateInfoKHR
x f :: Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b
f = Int
-> Int
-> (Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b) -> IO b)
-> (Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr RayTracingPipelineInterfaceCreateInfoKHR
p -> Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> RayTracingPipelineInterfaceCreateInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr RayTracingPipelineInterfaceCreateInfoKHR
p RayTracingPipelineInterfaceCreateInfoKHR
x (Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b
f Ptr RayTracingPipelineInterfaceCreateInfoKHR
p)
  pokeCStruct :: Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> RayTracingPipelineInterfaceCreateInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr RayTracingPipelineInterfaceCreateInfoKHR
p RayTracingPipelineInterfaceCreateInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RAY_TRACING_PIPELINE_INTERFACE_CREATE_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("bindInfoCount" ::: Word32
maxPayloadSize)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("bindInfoCount" ::: Word32
maxAttributeSize)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("bindInfoCount" ::: Word32
maxCallableSize)
    IO b
f
  cStructSize :: Int
cStructSize = 32
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr RayTracingPipelineInterfaceCreateInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr RayTracingPipelineInterfaceCreateInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_RAY_TRACING_PIPELINE_INTERFACE_CREATE_INFO_KHR)
    Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    Ptr ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("bindInfoCount" ::: Word32
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct RayTracingPipelineInterfaceCreateInfoKHR where
  peekCStruct :: Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> IO RayTracingPipelineInterfaceCreateInfoKHR
peekCStruct p :: Ptr RayTracingPipelineInterfaceCreateInfoKHR
p = do
    "bindInfoCount" ::: Word32
maxPayloadSize <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    "bindInfoCount" ::: Word32
maxAttributeSize <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
    "bindInfoCount" ::: Word32
maxCallableSize <- Ptr ("bindInfoCount" ::: Word32) -> IO ("bindInfoCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr RayTracingPipelineInterfaceCreateInfoKHR
p Ptr RayTracingPipelineInterfaceCreateInfoKHR
-> Int -> Ptr ("bindInfoCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
    RayTracingPipelineInterfaceCreateInfoKHR
-> IO RayTracingPipelineInterfaceCreateInfoKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RayTracingPipelineInterfaceCreateInfoKHR
 -> IO RayTracingPipelineInterfaceCreateInfoKHR)
-> RayTracingPipelineInterfaceCreateInfoKHR
-> IO RayTracingPipelineInterfaceCreateInfoKHR
forall a b. (a -> b) -> a -> b
$ ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> RayTracingPipelineInterfaceCreateInfoKHR
RayTracingPipelineInterfaceCreateInfoKHR
             "bindInfoCount" ::: Word32
maxPayloadSize "bindInfoCount" ::: Word32
maxAttributeSize "bindInfoCount" ::: Word32
maxCallableSize

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

instance Zero RayTracingPipelineInterfaceCreateInfoKHR where
  zero :: RayTracingPipelineInterfaceCreateInfoKHR
zero = ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> ("bindInfoCount" ::: Word32)
-> RayTracingPipelineInterfaceCreateInfoKHR
RayTracingPipelineInterfaceCreateInfoKHR
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero
           "bindInfoCount" ::: Word32
forall a. Zero a => a
zero


data DeviceOrHostAddressKHR
  = DeviceAddress DeviceAddress
  | HostAddress (Ptr ())
  deriving (Int -> DeviceOrHostAddressKHR -> ShowS
[DeviceOrHostAddressKHR] -> ShowS
DeviceOrHostAddressKHR -> String
(Int -> DeviceOrHostAddressKHR -> ShowS)
-> (DeviceOrHostAddressKHR -> String)
-> ([DeviceOrHostAddressKHR] -> ShowS)
-> Show DeviceOrHostAddressKHR
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeviceOrHostAddressKHR] -> ShowS
$cshowList :: [DeviceOrHostAddressKHR] -> ShowS
show :: DeviceOrHostAddressKHR -> String
$cshow :: DeviceOrHostAddressKHR -> String
showsPrec :: Int -> DeviceOrHostAddressKHR -> ShowS
$cshowsPrec :: Int -> DeviceOrHostAddressKHR -> ShowS
Show)

instance ToCStruct DeviceOrHostAddressKHR where
  withCStruct :: DeviceOrHostAddressKHR
-> (Ptr DeviceOrHostAddressKHR -> IO b) -> IO b
withCStruct x :: DeviceOrHostAddressKHR
x f :: Ptr DeviceOrHostAddressKHR -> IO b
f = Int -> Int -> (Ptr DeviceOrHostAddressKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 8 ((Ptr DeviceOrHostAddressKHR -> IO b) -> IO b)
-> (Ptr DeviceOrHostAddressKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeviceOrHostAddressKHR
p -> Ptr DeviceOrHostAddressKHR
-> DeviceOrHostAddressKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceOrHostAddressKHR
p DeviceOrHostAddressKHR
x (Ptr DeviceOrHostAddressKHR -> IO b
f Ptr DeviceOrHostAddressKHR
p)
  pokeCStruct :: Ptr DeviceOrHostAddressKHR -> DeviceOrHostAddressKHR -> IO a -> IO a
  pokeCStruct :: Ptr DeviceOrHostAddressKHR
-> DeviceOrHostAddressKHR -> IO a -> IO a
pokeCStruct p :: Ptr DeviceOrHostAddressKHR
p = (((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const) (((() -> IO a) -> IO a) -> IO a -> IO a)
-> (DeviceOrHostAddressKHR -> (() -> IO a) -> IO a)
-> DeviceOrHostAddressKHR
-> IO a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT a IO () -> (() -> IO a) -> IO a
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (ContT a IO () -> (() -> IO a) -> IO a)
-> (DeviceOrHostAddressKHR -> ContT a IO ())
-> DeviceOrHostAddressKHR
-> (() -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  \case
    DeviceAddress v :: "dataSize" ::: Word64
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DeviceOrHostAddressKHR -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Ptr b
castPtr @_ @DeviceAddress Ptr DeviceOrHostAddressKHR
p) ("dataSize" ::: Word64
v)
    HostAddress v :: "data" ::: Ptr ()
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DeviceOrHostAddressKHR -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr ()) Ptr DeviceOrHostAddressKHR
p) ("data" ::: Ptr ()
v)
  pokeZeroCStruct :: Ptr DeviceOrHostAddressKHR -> IO b -> IO b
  pokeZeroCStruct :: Ptr DeviceOrHostAddressKHR -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 8

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


data DeviceOrHostAddressConstKHR
  = DeviceAddressConst DeviceAddress
  | HostAddressConst (Ptr ())
  deriving (Int -> DeviceOrHostAddressConstKHR -> ShowS
[DeviceOrHostAddressConstKHR] -> ShowS
DeviceOrHostAddressConstKHR -> String
(Int -> DeviceOrHostAddressConstKHR -> ShowS)
-> (DeviceOrHostAddressConstKHR -> String)
-> ([DeviceOrHostAddressConstKHR] -> ShowS)
-> Show DeviceOrHostAddressConstKHR
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeviceOrHostAddressConstKHR] -> ShowS
$cshowList :: [DeviceOrHostAddressConstKHR] -> ShowS
show :: DeviceOrHostAddressConstKHR -> String
$cshow :: DeviceOrHostAddressConstKHR -> String
showsPrec :: Int -> DeviceOrHostAddressConstKHR -> ShowS
$cshowsPrec :: Int -> DeviceOrHostAddressConstKHR -> ShowS
Show)

instance ToCStruct DeviceOrHostAddressConstKHR where
  withCStruct :: DeviceOrHostAddressConstKHR
-> (Ptr DeviceOrHostAddressConstKHR -> IO b) -> IO b
withCStruct x :: DeviceOrHostAddressConstKHR
x f :: Ptr DeviceOrHostAddressConstKHR -> IO b
f = Int -> Int -> (Ptr DeviceOrHostAddressConstKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 8 8 ((Ptr DeviceOrHostAddressConstKHR -> IO b) -> IO b)
-> (Ptr DeviceOrHostAddressConstKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeviceOrHostAddressConstKHR
p -> Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceOrHostAddressConstKHR
p DeviceOrHostAddressConstKHR
x (Ptr DeviceOrHostAddressConstKHR -> IO b
f Ptr DeviceOrHostAddressConstKHR
p)
  pokeCStruct :: Ptr DeviceOrHostAddressConstKHR -> DeviceOrHostAddressConstKHR -> IO a -> IO a
  pokeCStruct :: Ptr DeviceOrHostAddressConstKHR
-> DeviceOrHostAddressConstKHR -> IO a -> IO a
pokeCStruct p :: Ptr DeviceOrHostAddressConstKHR
p = (((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const) (((() -> IO a) -> IO a) -> IO a -> IO a)
-> (DeviceOrHostAddressConstKHR -> (() -> IO a) -> IO a)
-> DeviceOrHostAddressConstKHR
-> IO a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT a IO () -> (() -> IO a) -> IO a
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (ContT a IO () -> (() -> IO a) -> IO a)
-> (DeviceOrHostAddressConstKHR -> ContT a IO ())
-> DeviceOrHostAddressConstKHR
-> (() -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  \case
    DeviceAddressConst v :: "dataSize" ::: Word64
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("dataSize" ::: Word64) -> ("dataSize" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DeviceOrHostAddressConstKHR -> Ptr ("dataSize" ::: Word64)
forall a b. Ptr a -> Ptr b
castPtr @_ @DeviceAddress Ptr DeviceOrHostAddressConstKHR
p) ("dataSize" ::: Word64
v)
    HostAddressConst v :: "data" ::: Ptr ()
v -> IO () -> ContT a IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT a IO ()) -> IO () -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("data" ::: Ptr ()) -> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr DeviceOrHostAddressConstKHR -> Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Ptr b
castPtr @_ @(Ptr ()) Ptr DeviceOrHostAddressConstKHR
p) ("data" ::: Ptr ()
v)
  pokeZeroCStruct :: Ptr DeviceOrHostAddressConstKHR -> IO b -> IO b
  pokeZeroCStruct :: Ptr DeviceOrHostAddressConstKHR -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
  cStructSize :: Int
cStructSize = 8
  cStructAlignment :: Int
cStructAlignment = 8

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


data AccelerationStructureGeometryDataKHR
  = Triangles AccelerationStructureGeometryTrianglesDataKHR
  | Aabbs AccelerationStructureGeometryAabbsDataKHR
  | Instances AccelerationStructureGeometryInstancesDataKHR
  deriving (Int -> AccelerationStructureGeometryDataKHR -> ShowS
[AccelerationStructureGeometryDataKHR] -> ShowS
AccelerationStructureGeometryDataKHR -> String
(Int -> AccelerationStructureGeometryDataKHR -> ShowS)
-> (AccelerationStructureGeometryDataKHR -> String)
-> ([AccelerationStructureGeometryDataKHR] -> ShowS)
-> Show AccelerationStructureGeometryDataKHR
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccelerationStructureGeometryDataKHR] -> ShowS
$cshowList :: [AccelerationStructureGeometryDataKHR] -> ShowS
show :: AccelerationStructureGeometryDataKHR -> String
$cshow :: AccelerationStructureGeometryDataKHR -> String
showsPrec :: Int -> AccelerationStructureGeometryDataKHR -> ShowS
$cshowsPrec :: Int -> AccelerationStructureGeometryDataKHR -> ShowS
Show)

instance ToCStruct AccelerationStructureGeometryDataKHR where
  withCStruct :: AccelerationStructureGeometryDataKHR
-> (Ptr AccelerationStructureGeometryDataKHR -> IO b) -> IO b
withCStruct x :: AccelerationStructureGeometryDataKHR
x f :: Ptr AccelerationStructureGeometryDataKHR -> IO b
f = Int
-> Int
-> (Ptr AccelerationStructureGeometryDataKHR -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 64 8 ((Ptr AccelerationStructureGeometryDataKHR -> IO b) -> IO b)
-> (Ptr AccelerationStructureGeometryDataKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AccelerationStructureGeometryDataKHR
p -> Ptr AccelerationStructureGeometryDataKHR
-> AccelerationStructureGeometryDataKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AccelerationStructureGeometryDataKHR
p AccelerationStructureGeometryDataKHR
x (Ptr AccelerationStructureGeometryDataKHR -> IO b
f Ptr AccelerationStructureGeometryDataKHR
p)
  pokeCStruct :: Ptr AccelerationStructureGeometryDataKHR -> AccelerationStructureGeometryDataKHR -> IO a -> IO a
  pokeCStruct :: Ptr AccelerationStructureGeometryDataKHR
-> AccelerationStructureGeometryDataKHR -> IO a -> IO a
pokeCStruct p :: Ptr AccelerationStructureGeometryDataKHR
p = (((() -> IO a) -> IO a) -> (IO a -> () -> IO a) -> IO a -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO a -> () -> IO a
forall a b. a -> b -> a
const) (((() -> IO a) -> IO a) -> IO a -> IO a)
-> (AccelerationStructureGeometryDataKHR -> (() -> IO a) -> IO a)
-> AccelerationStructureGeometryDataKHR
-> IO a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT a IO () -> (() -> IO a) -> IO a
forall k (r :: k) (m :: k -> *) a. ContT r m a -> (a -> m r) -> m r
runContT (ContT a IO () -> (() -> IO a) -> IO a)
-> (AccelerationStructureGeometryDataKHR -> ContT a IO ())
-> AccelerationStructureGeometryDataKHR
-> (() -> IO a)
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  \case
    Triangles v :: AccelerationStructureGeometryTrianglesDataKHR
v -> ((() -> IO a) -> IO a) -> ContT a IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO a) -> IO a) -> ContT a IO ())
-> ((() -> IO a) -> IO a) -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccelerationStructureGeometryTrianglesDataKHR
-> AccelerationStructureGeometryTrianglesDataKHR -> IO a -> IO a
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AccelerationStructureGeometryDataKHR
-> Ptr AccelerationStructureGeometryTrianglesDataKHR
forall a b. Ptr a -> Ptr b
castPtr @_ @AccelerationStructureGeometryTrianglesDataKHR Ptr AccelerationStructureGeometryDataKHR
p) (AccelerationStructureGeometryTrianglesDataKHR
v) (IO a -> IO a) -> ((() -> IO a) -> IO a) -> (() -> IO a) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO a) -> () -> IO a
forall a b. (a -> b) -> a -> b
$ ())
    Aabbs v :: AccelerationStructureGeometryAabbsDataKHR
v -> ((() -> IO a) -> IO a) -> ContT a IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO a) -> IO a) -> ContT a IO ())
-> ((() -> IO a) -> IO a) -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccelerationStructureGeometryAabbsDataKHR
-> AccelerationStructureGeometryAabbsDataKHR -> IO a -> IO a
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AccelerationStructureGeometryDataKHR
-> Ptr AccelerationStructureGeometryAabbsDataKHR
forall a b. Ptr a -> Ptr b
castPtr @_ @AccelerationStructureGeometryAabbsDataKHR Ptr AccelerationStructureGeometryDataKHR
p) (AccelerationStructureGeometryAabbsDataKHR
v) (IO a -> IO a) -> ((() -> IO a) -> IO a) -> (() -> IO a) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO a) -> () -> IO a
forall a b. (a -> b) -> a -> b
$ ())
    Instances v :: AccelerationStructureGeometryInstancesDataKHR
v -> ((() -> IO a) -> IO a) -> ContT a IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO a) -> IO a) -> ContT a IO ())
-> ((() -> IO a) -> IO a) -> ContT a IO ()
forall a b. (a -> b) -> a -> b
$ Ptr AccelerationStructureGeometryInstancesDataKHR
-> AccelerationStructureGeometryInstancesDataKHR -> IO a -> IO a
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr AccelerationStructureGeometryDataKHR
-> Ptr AccelerationStructureGeometryInstancesDataKHR
forall a b. Ptr a -> Ptr b
castPtr @_ @AccelerationStructureGeometryInstancesDataKHR Ptr AccelerationStructureGeometryDataKHR
p) (AccelerationStructureGeometryInstancesDataKHR
v) (IO a -> IO a) -> ((() -> IO a) -> IO a) -> (() -> IO a) -> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO a) -> () -> IO a
forall a b. (a -> b) -> a -> b
$ ())
  pokeZeroCStruct :: Ptr AccelerationStructureGeometryDataKHR -> IO b -> IO b
  pokeZeroCStruct :: Ptr AccelerationStructureGeometryDataKHR -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
  cStructSize :: Int
cStructSize = 64
  cStructAlignment :: Int
cStructAlignment = 8

instance Zero AccelerationStructureGeometryDataKHR where
  zero :: AccelerationStructureGeometryDataKHR
zero = AccelerationStructureGeometryTrianglesDataKHR
-> AccelerationStructureGeometryDataKHR
Triangles AccelerationStructureGeometryTrianglesDataKHR
forall a. Zero a => a
zero


-- | VkGeometryInstanceFlagBitsKHR - Instance flag bits
--
-- = Description
--
-- 'GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR' and
-- 'GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR' /must/ not be used in the same
-- flag.
--
-- = See Also
--
-- 'GeometryInstanceFlagsKHR'
newtype GeometryInstanceFlagBitsKHR = GeometryInstanceFlagBitsKHR Flags
  deriving newtype (GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
(GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool)
-> (GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool)
-> Eq GeometryInstanceFlagsKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
$c/= :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
== :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
$c== :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
Eq, Eq GeometryInstanceFlagsKHR
Eq GeometryInstanceFlagsKHR =>
(GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Ordering)
-> (GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool)
-> (GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool)
-> (GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool)
-> (GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool)
-> (GeometryInstanceFlagsKHR
    -> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR
    -> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR)
-> Ord GeometryInstanceFlagsKHR
GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Ordering
GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
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 :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
$cmin :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
max :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
$cmax :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
>= :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
$c>= :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
> :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
$c> :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
<= :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
$c<= :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
< :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
$c< :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Bool
compare :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Ordering
$ccompare :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> Ordering
$cp1Ord :: Eq GeometryInstanceFlagsKHR
Ord, Ptr b -> Int -> IO GeometryInstanceFlagsKHR
Ptr b -> Int -> GeometryInstanceFlagsKHR -> IO ()
Ptr GeometryInstanceFlagsKHR -> IO GeometryInstanceFlagsKHR
Ptr GeometryInstanceFlagsKHR -> Int -> IO GeometryInstanceFlagsKHR
Ptr GeometryInstanceFlagsKHR
-> Int -> GeometryInstanceFlagsKHR -> IO ()
Ptr GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> IO ()
GeometryInstanceFlagsKHR -> Int
(GeometryInstanceFlagsKHR -> Int)
-> (GeometryInstanceFlagsKHR -> Int)
-> (Ptr GeometryInstanceFlagsKHR
    -> Int -> IO GeometryInstanceFlagsKHR)
-> (Ptr GeometryInstanceFlagsKHR
    -> Int -> GeometryInstanceFlagsKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO GeometryInstanceFlagsKHR)
-> (forall b. Ptr b -> Int -> GeometryInstanceFlagsKHR -> IO ())
-> (Ptr GeometryInstanceFlagsKHR -> IO GeometryInstanceFlagsKHR)
-> (Ptr GeometryInstanceFlagsKHR
    -> GeometryInstanceFlagsKHR -> IO ())
-> Storable GeometryInstanceFlagsKHR
forall b. Ptr b -> Int -> IO GeometryInstanceFlagsKHR
forall b. Ptr b -> Int -> GeometryInstanceFlagsKHR -> 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 GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> IO ()
$cpoke :: Ptr GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR -> IO ()
peek :: Ptr GeometryInstanceFlagsKHR -> IO GeometryInstanceFlagsKHR
$cpeek :: Ptr GeometryInstanceFlagsKHR -> IO GeometryInstanceFlagsKHR
pokeByteOff :: Ptr b -> Int -> GeometryInstanceFlagsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> GeometryInstanceFlagsKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO GeometryInstanceFlagsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO GeometryInstanceFlagsKHR
pokeElemOff :: Ptr GeometryInstanceFlagsKHR
-> Int -> GeometryInstanceFlagsKHR -> IO ()
$cpokeElemOff :: Ptr GeometryInstanceFlagsKHR
-> Int -> GeometryInstanceFlagsKHR -> IO ()
peekElemOff :: Ptr GeometryInstanceFlagsKHR -> Int -> IO GeometryInstanceFlagsKHR
$cpeekElemOff :: Ptr GeometryInstanceFlagsKHR -> Int -> IO GeometryInstanceFlagsKHR
alignment :: GeometryInstanceFlagsKHR -> Int
$calignment :: GeometryInstanceFlagsKHR -> Int
sizeOf :: GeometryInstanceFlagsKHR -> Int
$csizeOf :: GeometryInstanceFlagsKHR -> Int
Storable, GeometryInstanceFlagsKHR
GeometryInstanceFlagsKHR -> Zero GeometryInstanceFlagsKHR
forall a. a -> Zero a
zero :: GeometryInstanceFlagsKHR
$czero :: GeometryInstanceFlagsKHR
Zero, Eq GeometryInstanceFlagsKHR
GeometryInstanceFlagsKHR
Eq GeometryInstanceFlagsKHR =>
(GeometryInstanceFlagsKHR
 -> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR
    -> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR
    -> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> GeometryInstanceFlagsKHR
-> (Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> Bool)
-> (GeometryInstanceFlagsKHR -> Maybe Int)
-> (GeometryInstanceFlagsKHR -> Int)
-> (GeometryInstanceFlagsKHR -> Bool)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR)
-> (GeometryInstanceFlagsKHR -> Int)
-> Bits GeometryInstanceFlagsKHR
Int -> GeometryInstanceFlagsKHR
GeometryInstanceFlagsKHR -> Bool
GeometryInstanceFlagsKHR -> Int
GeometryInstanceFlagsKHR -> Maybe Int
GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
GeometryInstanceFlagsKHR -> Int -> Bool
GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
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 :: GeometryInstanceFlagsKHR -> Int
$cpopCount :: GeometryInstanceFlagsKHR -> Int
rotateR :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$crotateR :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
rotateL :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$crotateL :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
unsafeShiftR :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$cunsafeShiftR :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
shiftR :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$cshiftR :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
unsafeShiftL :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$cunsafeShiftL :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
shiftL :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$cshiftL :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
isSigned :: GeometryInstanceFlagsKHR -> Bool
$cisSigned :: GeometryInstanceFlagsKHR -> Bool
bitSize :: GeometryInstanceFlagsKHR -> Int
$cbitSize :: GeometryInstanceFlagsKHR -> Int
bitSizeMaybe :: GeometryInstanceFlagsKHR -> Maybe Int
$cbitSizeMaybe :: GeometryInstanceFlagsKHR -> Maybe Int
testBit :: GeometryInstanceFlagsKHR -> Int -> Bool
$ctestBit :: GeometryInstanceFlagsKHR -> Int -> Bool
complementBit :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$ccomplementBit :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
clearBit :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$cclearBit :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
setBit :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$csetBit :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
bit :: Int -> GeometryInstanceFlagsKHR
$cbit :: Int -> GeometryInstanceFlagsKHR
zeroBits :: GeometryInstanceFlagsKHR
$czeroBits :: GeometryInstanceFlagsKHR
rotate :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$crotate :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
shift :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
$cshift :: GeometryInstanceFlagsKHR -> Int -> GeometryInstanceFlagsKHR
complement :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
$ccomplement :: GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
xor :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
$cxor :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
.|. :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
$c.|. :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
.&. :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
$c.&. :: GeometryInstanceFlagsKHR
-> GeometryInstanceFlagsKHR -> GeometryInstanceFlagsKHR
$cp1Bits :: Eq GeometryInstanceFlagsKHR
Bits)

-- | 'GEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR' disables face
-- culling for this instance.
pattern $bGEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR :: GeometryInstanceFlagsKHR
$mGEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR :: forall r.
GeometryInstanceFlagsKHR -> (Void# -> r) -> (Void# -> r) -> r
GEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR = GeometryInstanceFlagBitsKHR 0x00000001
-- | 'GEOMETRY_INSTANCE_TRIANGLE_FRONT_COUNTERCLOCKWISE_BIT_KHR' indicates
-- that the front face of the triangle for culling purposes is the face
-- that is counter clockwise in object space relative to the ray origin.
-- Because the facing is determined in object space, an instance transform
-- matrix does not change the winding, but a geometry transform does.
pattern $bGEOMETRY_INSTANCE_TRIANGLE_FRONT_COUNTERCLOCKWISE_BIT_KHR :: GeometryInstanceFlagsKHR
$mGEOMETRY_INSTANCE_TRIANGLE_FRONT_COUNTERCLOCKWISE_BIT_KHR :: forall r.
GeometryInstanceFlagsKHR -> (Void# -> r) -> (Void# -> r) -> r
GEOMETRY_INSTANCE_TRIANGLE_FRONT_COUNTERCLOCKWISE_BIT_KHR = GeometryInstanceFlagBitsKHR 0x00000002
-- | 'GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR' causes this instance to act as
-- though 'GEOMETRY_OPAQUE_BIT_KHR' were specified on all geometries
-- referenced by this instance. This behavior /can/ be overridden by the
-- SPIR-V @NoOpaqueKHR@ ray flag.
pattern $bGEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR :: GeometryInstanceFlagsKHR
$mGEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR :: forall r.
GeometryInstanceFlagsKHR -> (Void# -> r) -> (Void# -> r) -> r
GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR = GeometryInstanceFlagBitsKHR 0x00000004
-- | 'GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR' causes this instance to act
-- as though 'GEOMETRY_OPAQUE_BIT_KHR' were not specified on all geometries
-- referenced by this instance. This behavior /can/ be overridden by the
-- SPIR-V @OpaqueKHR@ ray flag.
pattern $bGEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR :: GeometryInstanceFlagsKHR
$mGEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR :: forall r.
GeometryInstanceFlagsKHR -> (Void# -> r) -> (Void# -> r) -> r
GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR = GeometryInstanceFlagBitsKHR 0x00000008

type GeometryInstanceFlagsKHR = GeometryInstanceFlagBitsKHR

instance Show GeometryInstanceFlagBitsKHR where
  showsPrec :: Int -> GeometryInstanceFlagsKHR -> ShowS
showsPrec p :: Int
p = \case
    GEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR -> String -> ShowS
showString "GEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR"
    GEOMETRY_INSTANCE_TRIANGLE_FRONT_COUNTERCLOCKWISE_BIT_KHR -> String -> ShowS
showString "GEOMETRY_INSTANCE_TRIANGLE_FRONT_COUNTERCLOCKWISE_BIT_KHR"
    GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR -> String -> ShowS
showString "GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR"
    GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR -> String -> ShowS
showString "GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR"
    GeometryInstanceFlagBitsKHR x :: "bindInfoCount" ::: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "GeometryInstanceFlagBitsKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("bindInfoCount" ::: Word32) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "bindInfoCount" ::: Word32
x)

instance Read GeometryInstanceFlagBitsKHR where
  readPrec :: ReadPrec GeometryInstanceFlagsKHR
readPrec = ReadPrec GeometryInstanceFlagsKHR
-> ReadPrec GeometryInstanceFlagsKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec GeometryInstanceFlagsKHR)]
-> ReadPrec GeometryInstanceFlagsKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("GEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR", GeometryInstanceFlagsKHR -> ReadPrec GeometryInstanceFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure GeometryInstanceFlagsKHR
GEOMETRY_INSTANCE_TRIANGLE_FACING_CULL_DISABLE_BIT_KHR)
                            , ("GEOMETRY_INSTANCE_TRIANGLE_FRONT_COUNTERCLOCKWISE_BIT_KHR", GeometryInstanceFlagsKHR -> ReadPrec GeometryInstanceFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure GeometryInstanceFlagsKHR
GEOMETRY_INSTANCE_TRIANGLE_FRONT_COUNTERCLOCKWISE_BIT_KHR)
                            , ("GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR", GeometryInstanceFlagsKHR -> ReadPrec GeometryInstanceFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure GeometryInstanceFlagsKHR
GEOMETRY_INSTANCE_FORCE_OPAQUE_BIT_KHR)
                            , ("GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR", GeometryInstanceFlagsKHR -> ReadPrec GeometryInstanceFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure GeometryInstanceFlagsKHR
GEOMETRY_INSTANCE_FORCE_NO_OPAQUE_BIT_KHR)]
                     ReadPrec GeometryInstanceFlagsKHR
-> ReadPrec GeometryInstanceFlagsKHR
-> ReadPrec GeometryInstanceFlagsKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec GeometryInstanceFlagsKHR
-> ReadPrec GeometryInstanceFlagsKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "GeometryInstanceFlagBitsKHR")
                       "bindInfoCount" ::: Word32
v <- ReadPrec ("bindInfoCount" ::: Word32)
-> ReadPrec ("bindInfoCount" ::: Word32)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec ("bindInfoCount" ::: Word32)
forall a. Read a => ReadPrec a
readPrec
                       GeometryInstanceFlagsKHR -> ReadPrec GeometryInstanceFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("bindInfoCount" ::: Word32) -> GeometryInstanceFlagsKHR
GeometryInstanceFlagBitsKHR "bindInfoCount" ::: Word32
v)))


-- | VkGeometryFlagBitsKHR - Bitmask specifying additional parameters for a
-- geometry
--
-- = See Also
--
-- 'GeometryFlagsKHR'
newtype GeometryFlagBitsKHR = GeometryFlagBitsKHR Flags
  deriving newtype (GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
(GeometryFlagsKHR -> GeometryFlagsKHR -> Bool)
-> (GeometryFlagsKHR -> GeometryFlagsKHR -> Bool)
-> Eq GeometryFlagsKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
$c/= :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
== :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
$c== :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
Eq, Eq GeometryFlagsKHR
Eq GeometryFlagsKHR =>
(GeometryFlagsKHR -> GeometryFlagsKHR -> Ordering)
-> (GeometryFlagsKHR -> GeometryFlagsKHR -> Bool)
-> (GeometryFlagsKHR -> GeometryFlagsKHR -> Bool)
-> (GeometryFlagsKHR -> GeometryFlagsKHR -> Bool)
-> (GeometryFlagsKHR -> GeometryFlagsKHR -> Bool)
-> (GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR)
-> Ord GeometryFlagsKHR
GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
GeometryFlagsKHR -> GeometryFlagsKHR -> Ordering
GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
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 :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
$cmin :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
max :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
$cmax :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
>= :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
$c>= :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
> :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
$c> :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
<= :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
$c<= :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
< :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
$c< :: GeometryFlagsKHR -> GeometryFlagsKHR -> Bool
compare :: GeometryFlagsKHR -> GeometryFlagsKHR -> Ordering
$ccompare :: GeometryFlagsKHR -> GeometryFlagsKHR -> Ordering
$cp1Ord :: Eq GeometryFlagsKHR
Ord, Ptr b -> Int -> IO GeometryFlagsKHR
Ptr b -> Int -> GeometryFlagsKHR -> IO ()
Ptr GeometryFlagsKHR -> IO GeometryFlagsKHR
Ptr GeometryFlagsKHR -> Int -> IO GeometryFlagsKHR
Ptr GeometryFlagsKHR -> Int -> GeometryFlagsKHR -> IO ()
Ptr GeometryFlagsKHR -> GeometryFlagsKHR -> IO ()
GeometryFlagsKHR -> Int
(GeometryFlagsKHR -> Int)
-> (GeometryFlagsKHR -> Int)
-> (Ptr GeometryFlagsKHR -> Int -> IO GeometryFlagsKHR)
-> (Ptr GeometryFlagsKHR -> Int -> GeometryFlagsKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO GeometryFlagsKHR)
-> (forall b. Ptr b -> Int -> GeometryFlagsKHR -> IO ())
-> (Ptr GeometryFlagsKHR -> IO GeometryFlagsKHR)
-> (Ptr GeometryFlagsKHR -> GeometryFlagsKHR -> IO ())
-> Storable GeometryFlagsKHR
forall b. Ptr b -> Int -> IO GeometryFlagsKHR
forall b. Ptr b -> Int -> GeometryFlagsKHR -> 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 GeometryFlagsKHR -> GeometryFlagsKHR -> IO ()
$cpoke :: Ptr GeometryFlagsKHR -> GeometryFlagsKHR -> IO ()
peek :: Ptr GeometryFlagsKHR -> IO GeometryFlagsKHR
$cpeek :: Ptr GeometryFlagsKHR -> IO GeometryFlagsKHR
pokeByteOff :: Ptr b -> Int -> GeometryFlagsKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> GeometryFlagsKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO GeometryFlagsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO GeometryFlagsKHR
pokeElemOff :: Ptr GeometryFlagsKHR -> Int -> GeometryFlagsKHR -> IO ()
$cpokeElemOff :: Ptr GeometryFlagsKHR -> Int -> GeometryFlagsKHR -> IO ()
peekElemOff :: Ptr GeometryFlagsKHR -> Int -> IO GeometryFlagsKHR
$cpeekElemOff :: Ptr GeometryFlagsKHR -> Int -> IO GeometryFlagsKHR
alignment :: GeometryFlagsKHR -> Int
$calignment :: GeometryFlagsKHR -> Int
sizeOf :: GeometryFlagsKHR -> Int
$csizeOf :: GeometryFlagsKHR -> Int
Storable, GeometryFlagsKHR
GeometryFlagsKHR -> Zero GeometryFlagsKHR
forall a. a -> Zero a
zero :: GeometryFlagsKHR
$czero :: GeometryFlagsKHR
Zero, Eq GeometryFlagsKHR
GeometryFlagsKHR
Eq GeometryFlagsKHR =>
(GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> GeometryFlagsKHR
-> (Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> Bool)
-> (GeometryFlagsKHR -> Maybe Int)
-> (GeometryFlagsKHR -> Int)
-> (GeometryFlagsKHR -> Bool)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int -> GeometryFlagsKHR)
-> (GeometryFlagsKHR -> Int)
-> Bits GeometryFlagsKHR
Int -> GeometryFlagsKHR
GeometryFlagsKHR -> Bool
GeometryFlagsKHR -> Int
GeometryFlagsKHR -> Maybe Int
GeometryFlagsKHR -> GeometryFlagsKHR
GeometryFlagsKHR -> Int -> Bool
GeometryFlagsKHR -> Int -> GeometryFlagsKHR
GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
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 :: GeometryFlagsKHR -> Int
$cpopCount :: GeometryFlagsKHR -> Int
rotateR :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$crotateR :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
rotateL :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$crotateL :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
unsafeShiftR :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$cunsafeShiftR :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
shiftR :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$cshiftR :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
unsafeShiftL :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$cunsafeShiftL :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
shiftL :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$cshiftL :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
isSigned :: GeometryFlagsKHR -> Bool
$cisSigned :: GeometryFlagsKHR -> Bool
bitSize :: GeometryFlagsKHR -> Int
$cbitSize :: GeometryFlagsKHR -> Int
bitSizeMaybe :: GeometryFlagsKHR -> Maybe Int
$cbitSizeMaybe :: GeometryFlagsKHR -> Maybe Int
testBit :: GeometryFlagsKHR -> Int -> Bool
$ctestBit :: GeometryFlagsKHR -> Int -> Bool
complementBit :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$ccomplementBit :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
clearBit :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$cclearBit :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
setBit :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$csetBit :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
bit :: Int -> GeometryFlagsKHR
$cbit :: Int -> GeometryFlagsKHR
zeroBits :: GeometryFlagsKHR
$czeroBits :: GeometryFlagsKHR
rotate :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$crotate :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
shift :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
$cshift :: GeometryFlagsKHR -> Int -> GeometryFlagsKHR
complement :: GeometryFlagsKHR -> GeometryFlagsKHR
$ccomplement :: GeometryFlagsKHR -> GeometryFlagsKHR
xor :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
$cxor :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
.|. :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
$c.|. :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
.&. :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
$c.&. :: GeometryFlagsKHR -> GeometryFlagsKHR -> GeometryFlagsKHR
$cp1Bits :: Eq GeometryFlagsKHR
Bits)

-- | 'GEOMETRY_OPAQUE_BIT_KHR' indicates that this geometry does not invoke
-- the any-hit shaders even if present in a hit group.
pattern $bGEOMETRY_OPAQUE_BIT_KHR :: GeometryFlagsKHR
$mGEOMETRY_OPAQUE_BIT_KHR :: forall r. GeometryFlagsKHR -> (Void# -> r) -> (Void# -> r) -> r
GEOMETRY_OPAQUE_BIT_KHR = GeometryFlagBitsKHR 0x00000001
-- | 'GEOMETRY_NO_DUPLICATE_ANY_HIT_INVOCATION_BIT_KHR' indicates that the
-- implementation /must/ only call the any-hit shader a single time for
-- each primitive in this geometry. If this bit is absent an implementation
-- /may/ invoke the any-hit shader more than once for this geometry.
pattern $bGEOMETRY_NO_DUPLICATE_ANY_HIT_INVOCATION_BIT_KHR :: GeometryFlagsKHR
$mGEOMETRY_NO_DUPLICATE_ANY_HIT_INVOCATION_BIT_KHR :: forall r. GeometryFlagsKHR -> (Void# -> r) -> (Void# -> r) -> r
GEOMETRY_NO_DUPLICATE_ANY_HIT_INVOCATION_BIT_KHR = GeometryFlagBitsKHR 0x00000002

type GeometryFlagsKHR = GeometryFlagBitsKHR

instance Show GeometryFlagBitsKHR where
  showsPrec :: Int -> GeometryFlagsKHR -> ShowS
showsPrec p :: Int
p = \case
    GEOMETRY_OPAQUE_BIT_KHR -> String -> ShowS
showString "GEOMETRY_OPAQUE_BIT_KHR"
    GEOMETRY_NO_DUPLICATE_ANY_HIT_INVOCATION_BIT_KHR -> String -> ShowS
showString "GEOMETRY_NO_DUPLICATE_ANY_HIT_INVOCATION_BIT_KHR"
    GeometryFlagBitsKHR x :: "bindInfoCount" ::: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "GeometryFlagBitsKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("bindInfoCount" ::: Word32) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "bindInfoCount" ::: Word32
x)

instance Read GeometryFlagBitsKHR where
  readPrec :: ReadPrec GeometryFlagsKHR
readPrec = ReadPrec GeometryFlagsKHR -> ReadPrec GeometryFlagsKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec GeometryFlagsKHR)] -> ReadPrec GeometryFlagsKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("GEOMETRY_OPAQUE_BIT_KHR", GeometryFlagsKHR -> ReadPrec GeometryFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure GeometryFlagsKHR
GEOMETRY_OPAQUE_BIT_KHR)
                            , ("GEOMETRY_NO_DUPLICATE_ANY_HIT_INVOCATION_BIT_KHR", GeometryFlagsKHR -> ReadPrec GeometryFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure GeometryFlagsKHR
GEOMETRY_NO_DUPLICATE_ANY_HIT_INVOCATION_BIT_KHR)]
                     ReadPrec GeometryFlagsKHR
-> ReadPrec GeometryFlagsKHR -> ReadPrec GeometryFlagsKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec GeometryFlagsKHR -> ReadPrec GeometryFlagsKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "GeometryFlagBitsKHR")
                       "bindInfoCount" ::: Word32
v <- ReadPrec ("bindInfoCount" ::: Word32)
-> ReadPrec ("bindInfoCount" ::: Word32)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec ("bindInfoCount" ::: Word32)
forall a. Read a => ReadPrec a
readPrec
                       GeometryFlagsKHR -> ReadPrec GeometryFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("bindInfoCount" ::: Word32) -> GeometryFlagsKHR
GeometryFlagBitsKHR "bindInfoCount" ::: Word32
v)))


-- | VkBuildAccelerationStructureFlagBitsKHR - Bitmask specifying additional
-- parameters for acceleration structure builds
--
-- = Description
--
-- Note
--
-- 'BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR' and
-- 'BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR' /may/ take more
-- time and memory than a normal build, and so /should/ only be used when
-- those features are needed.
--
-- = See Also
--
-- 'BuildAccelerationStructureFlagsKHR'
newtype BuildAccelerationStructureFlagBitsKHR = BuildAccelerationStructureFlagBitsKHR Flags
  deriving newtype (BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
(BuildAccelerationStructureFlagsKHR
 -> BuildAccelerationStructureFlagsKHR -> Bool)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR -> Bool)
-> Eq BuildAccelerationStructureFlagsKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
$c/= :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
== :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
$c== :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
Eq, Eq BuildAccelerationStructureFlagsKHR
Eq BuildAccelerationStructureFlagsKHR =>
(BuildAccelerationStructureFlagsKHR
 -> BuildAccelerationStructureFlagsKHR -> Ordering)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR -> Bool)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR -> Bool)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR -> Bool)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR -> Bool)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR)
-> Ord BuildAccelerationStructureFlagsKHR
BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Ordering
BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
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 :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
$cmin :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
max :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
$cmax :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
>= :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
$c>= :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
> :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
$c> :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
<= :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
$c<= :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
< :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
$c< :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Bool
compare :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Ordering
$ccompare :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> Ordering
$cp1Ord :: Eq BuildAccelerationStructureFlagsKHR
Ord, Ptr b -> Int -> IO BuildAccelerationStructureFlagsKHR
Ptr b -> Int -> BuildAccelerationStructureFlagsKHR -> IO ()
Ptr BuildAccelerationStructureFlagsKHR
-> IO BuildAccelerationStructureFlagsKHR
Ptr BuildAccelerationStructureFlagsKHR
-> Int -> IO BuildAccelerationStructureFlagsKHR
Ptr BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR -> IO ()
Ptr BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> IO ()
BuildAccelerationStructureFlagsKHR -> Int
(BuildAccelerationStructureFlagsKHR -> Int)
-> (BuildAccelerationStructureFlagsKHR -> Int)
-> (Ptr BuildAccelerationStructureFlagsKHR
    -> Int -> IO BuildAccelerationStructureFlagsKHR)
-> (Ptr BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR -> IO ())
-> (forall b.
    Ptr b -> Int -> IO BuildAccelerationStructureFlagsKHR)
-> (forall b.
    Ptr b -> Int -> BuildAccelerationStructureFlagsKHR -> IO ())
-> (Ptr BuildAccelerationStructureFlagsKHR
    -> IO BuildAccelerationStructureFlagsKHR)
-> (Ptr BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR -> IO ())
-> Storable BuildAccelerationStructureFlagsKHR
forall b. Ptr b -> Int -> IO BuildAccelerationStructureFlagsKHR
forall b.
Ptr b -> Int -> BuildAccelerationStructureFlagsKHR -> 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 BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> IO ()
$cpoke :: Ptr BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR -> IO ()
peek :: Ptr BuildAccelerationStructureFlagsKHR
-> IO BuildAccelerationStructureFlagsKHR
$cpeek :: Ptr BuildAccelerationStructureFlagsKHR
-> IO BuildAccelerationStructureFlagsKHR
pokeByteOff :: Ptr b -> Int -> BuildAccelerationStructureFlagsKHR -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> BuildAccelerationStructureFlagsKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO BuildAccelerationStructureFlagsKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO BuildAccelerationStructureFlagsKHR
pokeElemOff :: Ptr BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR -> IO ()
$cpokeElemOff :: Ptr BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR -> IO ()
peekElemOff :: Ptr BuildAccelerationStructureFlagsKHR
-> Int -> IO BuildAccelerationStructureFlagsKHR
$cpeekElemOff :: Ptr BuildAccelerationStructureFlagsKHR
-> Int -> IO BuildAccelerationStructureFlagsKHR
alignment :: BuildAccelerationStructureFlagsKHR -> Int
$calignment :: BuildAccelerationStructureFlagsKHR -> Int
sizeOf :: BuildAccelerationStructureFlagsKHR -> Int
$csizeOf :: BuildAccelerationStructureFlagsKHR -> Int
Storable, BuildAccelerationStructureFlagsKHR
BuildAccelerationStructureFlagsKHR
-> Zero BuildAccelerationStructureFlagsKHR
forall a. a -> Zero a
zero :: BuildAccelerationStructureFlagsKHR
$czero :: BuildAccelerationStructureFlagsKHR
Zero, Eq BuildAccelerationStructureFlagsKHR
BuildAccelerationStructureFlagsKHR
Eq BuildAccelerationStructureFlagsKHR =>
(BuildAccelerationStructureFlagsKHR
 -> BuildAccelerationStructureFlagsKHR
 -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> BuildAccelerationStructureFlagsKHR
-> (Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR -> Int -> Bool)
-> (BuildAccelerationStructureFlagsKHR -> Maybe Int)
-> (BuildAccelerationStructureFlagsKHR -> Int)
-> (BuildAccelerationStructureFlagsKHR -> Bool)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR
    -> Int -> BuildAccelerationStructureFlagsKHR)
-> (BuildAccelerationStructureFlagsKHR -> Int)
-> Bits BuildAccelerationStructureFlagsKHR
Int -> BuildAccelerationStructureFlagsKHR
BuildAccelerationStructureFlagsKHR -> Bool
BuildAccelerationStructureFlagsKHR -> Int
BuildAccelerationStructureFlagsKHR -> Maybe Int
BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
BuildAccelerationStructureFlagsKHR -> Int -> Bool
BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
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 :: BuildAccelerationStructureFlagsKHR -> Int
$cpopCount :: BuildAccelerationStructureFlagsKHR -> Int
rotateR :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$crotateR :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
rotateL :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$crotateL :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
unsafeShiftR :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$cunsafeShiftR :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
shiftR :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$cshiftR :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
unsafeShiftL :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$cunsafeShiftL :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
shiftL :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$cshiftL :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
isSigned :: BuildAccelerationStructureFlagsKHR -> Bool
$cisSigned :: BuildAccelerationStructureFlagsKHR -> Bool
bitSize :: BuildAccelerationStructureFlagsKHR -> Int
$cbitSize :: BuildAccelerationStructureFlagsKHR -> Int
bitSizeMaybe :: BuildAccelerationStructureFlagsKHR -> Maybe Int
$cbitSizeMaybe :: BuildAccelerationStructureFlagsKHR -> Maybe Int
testBit :: BuildAccelerationStructureFlagsKHR -> Int -> Bool
$ctestBit :: BuildAccelerationStructureFlagsKHR -> Int -> Bool
complementBit :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$ccomplementBit :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
clearBit :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$cclearBit :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
setBit :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$csetBit :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
bit :: Int -> BuildAccelerationStructureFlagsKHR
$cbit :: Int -> BuildAccelerationStructureFlagsKHR
zeroBits :: BuildAccelerationStructureFlagsKHR
$czeroBits :: BuildAccelerationStructureFlagsKHR
rotate :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$crotate :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
shift :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
$cshift :: BuildAccelerationStructureFlagsKHR
-> Int -> BuildAccelerationStructureFlagsKHR
complement :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
$ccomplement :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
xor :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
$cxor :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
.|. :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
$c.|. :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
.&. :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
$c.&. :: BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
-> BuildAccelerationStructureFlagsKHR
$cp1Bits :: Eq BuildAccelerationStructureFlagsKHR
Bits)

-- | 'BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR' indicates that the
-- specified acceleration structure /can/ be updated with @update@ of
-- 'Vulkan.Core10.FundamentalTypes.TRUE' in
-- 'cmdBuildAccelerationStructureKHR' or
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdBuildAccelerationStructureNV' .
pattern $bBUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR :: BuildAccelerationStructureFlagsKHR
$mBUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR :: forall r.
BuildAccelerationStructureFlagsKHR
-> (Void# -> r) -> (Void# -> r) -> r
BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR = BuildAccelerationStructureFlagBitsKHR 0x00000001
-- | 'BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR' indicates that
-- the specified acceleration structure /can/ act as the source for a copy
-- acceleration structure command with @mode@ of
-- 'COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR' to produce a compacted
-- acceleration structure.
pattern $bBUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR :: BuildAccelerationStructureFlagsKHR
$mBUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR :: forall r.
BuildAccelerationStructureFlagsKHR
-> (Void# -> r) -> (Void# -> r) -> r
BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR = BuildAccelerationStructureFlagBitsKHR 0x00000002
-- | 'BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR' indicates that
-- the given acceleration structure build /should/ prioritize trace
-- performance over build time.
pattern $bBUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR :: BuildAccelerationStructureFlagsKHR
$mBUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR :: forall r.
BuildAccelerationStructureFlagsKHR
-> (Void# -> r) -> (Void# -> r) -> r
BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR = BuildAccelerationStructureFlagBitsKHR 0x00000004
-- | 'BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR' indicates that
-- the given acceleration structure build /should/ prioritize build time
-- over trace performance.
pattern $bBUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR :: BuildAccelerationStructureFlagsKHR
$mBUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR :: forall r.
BuildAccelerationStructureFlagsKHR
-> (Void# -> r) -> (Void# -> r) -> r
BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR = BuildAccelerationStructureFlagBitsKHR 0x00000008
-- | 'BUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR' indicates that this
-- acceleration structure /should/ minimize the size of the scratch memory
-- and the final result build, potentially at the expense of build time or
-- trace performance.
pattern $bBUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR :: BuildAccelerationStructureFlagsKHR
$mBUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR :: forall r.
BuildAccelerationStructureFlagsKHR
-> (Void# -> r) -> (Void# -> r) -> r
BUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR = BuildAccelerationStructureFlagBitsKHR 0x00000010

type BuildAccelerationStructureFlagsKHR = BuildAccelerationStructureFlagBitsKHR

instance Show BuildAccelerationStructureFlagBitsKHR where
  showsPrec :: Int -> BuildAccelerationStructureFlagsKHR -> ShowS
showsPrec p :: Int
p = \case
    BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR -> String -> ShowS
showString "BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR"
    BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR -> String -> ShowS
showString "BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR"
    BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR -> String -> ShowS
showString "BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR"
    BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR -> String -> ShowS
showString "BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR"
    BUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR -> String -> ShowS
showString "BUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR"
    BuildAccelerationStructureFlagBitsKHR x :: "bindInfoCount" ::: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "BuildAccelerationStructureFlagBitsKHR 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("bindInfoCount" ::: Word32) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "bindInfoCount" ::: Word32
x)

instance Read BuildAccelerationStructureFlagBitsKHR where
  readPrec :: ReadPrec BuildAccelerationStructureFlagsKHR
readPrec = ReadPrec BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec BuildAccelerationStructureFlagsKHR)]
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR", BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure BuildAccelerationStructureFlagsKHR
BUILD_ACCELERATION_STRUCTURE_ALLOW_UPDATE_BIT_KHR)
                            , ("BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR", BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure BuildAccelerationStructureFlagsKHR
BUILD_ACCELERATION_STRUCTURE_ALLOW_COMPACTION_BIT_KHR)
                            , ("BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR", BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure BuildAccelerationStructureFlagsKHR
BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_TRACE_BIT_KHR)
                            , ("BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR", BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure BuildAccelerationStructureFlagsKHR
BUILD_ACCELERATION_STRUCTURE_PREFER_FAST_BUILD_BIT_KHR)
                            , ("BUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR", BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure BuildAccelerationStructureFlagsKHR
BUILD_ACCELERATION_STRUCTURE_LOW_MEMORY_BIT_KHR)]
                     ReadPrec BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "BuildAccelerationStructureFlagBitsKHR")
                       "bindInfoCount" ::: Word32
v <- ReadPrec ("bindInfoCount" ::: Word32)
-> ReadPrec ("bindInfoCount" ::: Word32)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec ("bindInfoCount" ::: Word32)
forall a. Read a => ReadPrec a
readPrec
                       BuildAccelerationStructureFlagsKHR
-> ReadPrec BuildAccelerationStructureFlagsKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("bindInfoCount" ::: Word32) -> BuildAccelerationStructureFlagsKHR
BuildAccelerationStructureFlagBitsKHR "bindInfoCount" ::: Word32
v)))


-- | VkCopyAccelerationStructureModeKHR - Acceleration structure copy mode
--
-- = See Also
--
-- 'CopyAccelerationStructureInfoKHR',
-- 'CopyAccelerationStructureToMemoryInfoKHR',
-- 'CopyMemoryToAccelerationStructureInfoKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.cmdCopyAccelerationStructureNV'
newtype CopyAccelerationStructureModeKHR = CopyAccelerationStructureModeKHR Int32
  deriving newtype (CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
(CopyAccelerationStructureModeKHR
 -> CopyAccelerationStructureModeKHR -> Bool)
-> (CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR -> Bool)
-> Eq CopyAccelerationStructureModeKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
$c/= :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
== :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
$c== :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
Eq, Eq CopyAccelerationStructureModeKHR
Eq CopyAccelerationStructureModeKHR =>
(CopyAccelerationStructureModeKHR
 -> CopyAccelerationStructureModeKHR -> Ordering)
-> (CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR -> Bool)
-> (CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR -> Bool)
-> (CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR -> Bool)
-> (CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR -> Bool)
-> (CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR)
-> (CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR)
-> Ord CopyAccelerationStructureModeKHR
CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Ordering
CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
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 :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
$cmin :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
max :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
$cmax :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR
>= :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
$c>= :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
> :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
$c> :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
<= :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
$c<= :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
< :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
$c< :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Bool
compare :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Ordering
$ccompare :: CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> Ordering
$cp1Ord :: Eq CopyAccelerationStructureModeKHR
Ord, Ptr b -> Int -> IO CopyAccelerationStructureModeKHR
Ptr b -> Int -> CopyAccelerationStructureModeKHR -> IO ()
Ptr CopyAccelerationStructureModeKHR
-> IO CopyAccelerationStructureModeKHR
Ptr CopyAccelerationStructureModeKHR
-> Int -> IO CopyAccelerationStructureModeKHR
Ptr CopyAccelerationStructureModeKHR
-> Int -> CopyAccelerationStructureModeKHR -> IO ()
Ptr CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> IO ()
CopyAccelerationStructureModeKHR -> Int
(CopyAccelerationStructureModeKHR -> Int)
-> (CopyAccelerationStructureModeKHR -> Int)
-> (Ptr CopyAccelerationStructureModeKHR
    -> Int -> IO CopyAccelerationStructureModeKHR)
-> (Ptr CopyAccelerationStructureModeKHR
    -> Int -> CopyAccelerationStructureModeKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO CopyAccelerationStructureModeKHR)
-> (forall b.
    Ptr b -> Int -> CopyAccelerationStructureModeKHR -> IO ())
-> (Ptr CopyAccelerationStructureModeKHR
    -> IO CopyAccelerationStructureModeKHR)
-> (Ptr CopyAccelerationStructureModeKHR
    -> CopyAccelerationStructureModeKHR -> IO ())
-> Storable CopyAccelerationStructureModeKHR
forall b. Ptr b -> Int -> IO CopyAccelerationStructureModeKHR
forall b. Ptr b -> Int -> CopyAccelerationStructureModeKHR -> 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 CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> IO ()
$cpoke :: Ptr CopyAccelerationStructureModeKHR
-> CopyAccelerationStructureModeKHR -> IO ()
peek :: Ptr CopyAccelerationStructureModeKHR
-> IO CopyAccelerationStructureModeKHR
$cpeek :: Ptr CopyAccelerationStructureModeKHR
-> IO CopyAccelerationStructureModeKHR
pokeByteOff :: Ptr b -> Int -> CopyAccelerationStructureModeKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> CopyAccelerationStructureModeKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO CopyAccelerationStructureModeKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO CopyAccelerationStructureModeKHR
pokeElemOff :: Ptr CopyAccelerationStructureModeKHR
-> Int -> CopyAccelerationStructureModeKHR -> IO ()
$cpokeElemOff :: Ptr CopyAccelerationStructureModeKHR
-> Int -> CopyAccelerationStructureModeKHR -> IO ()
peekElemOff :: Ptr CopyAccelerationStructureModeKHR
-> Int -> IO CopyAccelerationStructureModeKHR
$cpeekElemOff :: Ptr CopyAccelerationStructureModeKHR
-> Int -> IO CopyAccelerationStructureModeKHR
alignment :: CopyAccelerationStructureModeKHR -> Int
$calignment :: CopyAccelerationStructureModeKHR -> Int
sizeOf :: CopyAccelerationStructureModeKHR -> Int
$csizeOf :: CopyAccelerationStructureModeKHR -> Int
Storable, CopyAccelerationStructureModeKHR
CopyAccelerationStructureModeKHR
-> Zero CopyAccelerationStructureModeKHR
forall a. a -> Zero a
zero :: CopyAccelerationStructureModeKHR
$czero :: CopyAccelerationStructureModeKHR
Zero)

-- | 'COPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR' creates a direct copy of
-- the acceleration structure specified in @src@ into the one specified by
-- @dst@. The @dst@ acceleration structure /must/ have been created with
-- the same parameters as @src@.
pattern $bCOPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR :: CopyAccelerationStructureModeKHR
$mCOPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR :: forall r.
CopyAccelerationStructureModeKHR
-> (Void# -> r) -> (Void# -> r) -> r
COPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR = CopyAccelerationStructureModeKHR 0
-- | 'COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR' creates a more compact
-- version of an acceleration structure @src@ into @dst@. The acceleration
-- structure @dst@ /must/ have been created with a @compactedSize@
-- corresponding to the one returned by
-- 'cmdWriteAccelerationStructuresPropertiesKHR' after the build of the
-- acceleration structure specified by @src@.
pattern $bCOPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR :: CopyAccelerationStructureModeKHR
$mCOPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR :: forall r.
CopyAccelerationStructureModeKHR
-> (Void# -> r) -> (Void# -> r) -> r
COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR = CopyAccelerationStructureModeKHR 1
-- | 'COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR' serializes the
-- acceleration structure to a semi-opaque format which can be reloaded on
-- a compatible implementation.
pattern $bCOPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR :: CopyAccelerationStructureModeKHR
$mCOPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR :: forall r.
CopyAccelerationStructureModeKHR
-> (Void# -> r) -> (Void# -> r) -> r
COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR = CopyAccelerationStructureModeKHR 2
-- | 'COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR' deserializes the
-- semi-opaque serialization format in the buffer to the acceleration
-- structure.
pattern $bCOPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR :: CopyAccelerationStructureModeKHR
$mCOPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR :: forall r.
CopyAccelerationStructureModeKHR
-> (Void# -> r) -> (Void# -> r) -> r
COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR = CopyAccelerationStructureModeKHR 3
{-# complete COPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR,
             COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR,
             COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR,
             COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR :: CopyAccelerationStructureModeKHR #-}

instance Show CopyAccelerationStructureModeKHR where
  showsPrec :: Int -> CopyAccelerationStructureModeKHR -> ShowS
showsPrec p :: Int
p = \case
    COPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR -> String -> ShowS
showString "COPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR"
    COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR -> String -> ShowS
showString "COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR"
    COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR -> String -> ShowS
showString "COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR"
    COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR -> String -> ShowS
showString "COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR"
    CopyAccelerationStructureModeKHR x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "CopyAccelerationStructureModeKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read CopyAccelerationStructureModeKHR where
  readPrec :: ReadPrec CopyAccelerationStructureModeKHR
readPrec = ReadPrec CopyAccelerationStructureModeKHR
-> ReadPrec CopyAccelerationStructureModeKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec CopyAccelerationStructureModeKHR)]
-> ReadPrec CopyAccelerationStructureModeKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("COPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR", CopyAccelerationStructureModeKHR
-> ReadPrec CopyAccelerationStructureModeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure CopyAccelerationStructureModeKHR
COPY_ACCELERATION_STRUCTURE_MODE_CLONE_KHR)
                            , ("COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR", CopyAccelerationStructureModeKHR
-> ReadPrec CopyAccelerationStructureModeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure CopyAccelerationStructureModeKHR
COPY_ACCELERATION_STRUCTURE_MODE_COMPACT_KHR)
                            , ("COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR", CopyAccelerationStructureModeKHR
-> ReadPrec CopyAccelerationStructureModeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure CopyAccelerationStructureModeKHR
COPY_ACCELERATION_STRUCTURE_MODE_SERIALIZE_KHR)
                            , ("COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR", CopyAccelerationStructureModeKHR
-> ReadPrec CopyAccelerationStructureModeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure CopyAccelerationStructureModeKHR
COPY_ACCELERATION_STRUCTURE_MODE_DESERIALIZE_KHR)]
                     ReadPrec CopyAccelerationStructureModeKHR
-> ReadPrec CopyAccelerationStructureModeKHR
-> ReadPrec CopyAccelerationStructureModeKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec CopyAccelerationStructureModeKHR
-> ReadPrec CopyAccelerationStructureModeKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "CopyAccelerationStructureModeKHR")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       CopyAccelerationStructureModeKHR
-> ReadPrec CopyAccelerationStructureModeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> CopyAccelerationStructureModeKHR
CopyAccelerationStructureModeKHR Int32
v)))


-- | VkAccelerationStructureTypeKHR - Type of acceleration structure
--
-- = See Also
--
-- 'AccelerationStructureBuildGeometryInfoKHR',
-- 'AccelerationStructureCreateInfoKHR'
newtype AccelerationStructureTypeKHR = AccelerationStructureTypeKHR Int32
  deriving newtype (AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
(AccelerationStructureTypeKHR
 -> AccelerationStructureTypeKHR -> Bool)
-> (AccelerationStructureTypeKHR
    -> AccelerationStructureTypeKHR -> Bool)
-> Eq AccelerationStructureTypeKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
$c/= :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
== :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
$c== :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
Eq, Eq AccelerationStructureTypeKHR
Eq AccelerationStructureTypeKHR =>
(AccelerationStructureTypeKHR
 -> AccelerationStructureTypeKHR -> Ordering)
-> (AccelerationStructureTypeKHR
    -> AccelerationStructureTypeKHR -> Bool)
-> (AccelerationStructureTypeKHR
    -> AccelerationStructureTypeKHR -> Bool)
-> (AccelerationStructureTypeKHR
    -> AccelerationStructureTypeKHR -> Bool)
-> (AccelerationStructureTypeKHR
    -> AccelerationStructureTypeKHR -> Bool)
-> (AccelerationStructureTypeKHR
    -> AccelerationStructureTypeKHR -> AccelerationStructureTypeKHR)
-> (AccelerationStructureTypeKHR
    -> AccelerationStructureTypeKHR -> AccelerationStructureTypeKHR)
-> Ord AccelerationStructureTypeKHR
AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Ordering
AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> AccelerationStructureTypeKHR
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 :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> AccelerationStructureTypeKHR
$cmin :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> AccelerationStructureTypeKHR
max :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> AccelerationStructureTypeKHR
$cmax :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> AccelerationStructureTypeKHR
>= :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
$c>= :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
> :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
$c> :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
<= :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
$c<= :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
< :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
$c< :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Bool
compare :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Ordering
$ccompare :: AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> Ordering
$cp1Ord :: Eq AccelerationStructureTypeKHR
Ord, Ptr b -> Int -> IO AccelerationStructureTypeKHR
Ptr b -> Int -> AccelerationStructureTypeKHR -> IO ()
Ptr AccelerationStructureTypeKHR -> IO AccelerationStructureTypeKHR
Ptr AccelerationStructureTypeKHR
-> Int -> IO AccelerationStructureTypeKHR
Ptr AccelerationStructureTypeKHR
-> Int -> AccelerationStructureTypeKHR -> IO ()
Ptr AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> IO ()
AccelerationStructureTypeKHR -> Int
(AccelerationStructureTypeKHR -> Int)
-> (AccelerationStructureTypeKHR -> Int)
-> (Ptr AccelerationStructureTypeKHR
    -> Int -> IO AccelerationStructureTypeKHR)
-> (Ptr AccelerationStructureTypeKHR
    -> Int -> AccelerationStructureTypeKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO AccelerationStructureTypeKHR)
-> (forall b.
    Ptr b -> Int -> AccelerationStructureTypeKHR -> IO ())
-> (Ptr AccelerationStructureTypeKHR
    -> IO AccelerationStructureTypeKHR)
-> (Ptr AccelerationStructureTypeKHR
    -> AccelerationStructureTypeKHR -> IO ())
-> Storable AccelerationStructureTypeKHR
forall b. Ptr b -> Int -> IO AccelerationStructureTypeKHR
forall b. Ptr b -> Int -> AccelerationStructureTypeKHR -> 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 AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> IO ()
$cpoke :: Ptr AccelerationStructureTypeKHR
-> AccelerationStructureTypeKHR -> IO ()
peek :: Ptr AccelerationStructureTypeKHR -> IO AccelerationStructureTypeKHR
$cpeek :: Ptr AccelerationStructureTypeKHR -> IO AccelerationStructureTypeKHR
pokeByteOff :: Ptr b -> Int -> AccelerationStructureTypeKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AccelerationStructureTypeKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO AccelerationStructureTypeKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureTypeKHR
pokeElemOff :: Ptr AccelerationStructureTypeKHR
-> Int -> AccelerationStructureTypeKHR -> IO ()
$cpokeElemOff :: Ptr AccelerationStructureTypeKHR
-> Int -> AccelerationStructureTypeKHR -> IO ()
peekElemOff :: Ptr AccelerationStructureTypeKHR
-> Int -> IO AccelerationStructureTypeKHR
$cpeekElemOff :: Ptr AccelerationStructureTypeKHR
-> Int -> IO AccelerationStructureTypeKHR
alignment :: AccelerationStructureTypeKHR -> Int
$calignment :: AccelerationStructureTypeKHR -> Int
sizeOf :: AccelerationStructureTypeKHR -> Int
$csizeOf :: AccelerationStructureTypeKHR -> Int
Storable, AccelerationStructureTypeKHR
AccelerationStructureTypeKHR -> Zero AccelerationStructureTypeKHR
forall a. a -> Zero a
zero :: AccelerationStructureTypeKHR
$czero :: AccelerationStructureTypeKHR
Zero)

-- | 'ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR' is a top-level acceleration
-- structure containing instance data referring to bottom-level
-- acceleration structures.
pattern $bACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR :: AccelerationStructureTypeKHR
$mACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR :: forall r.
AccelerationStructureTypeKHR -> (Void# -> r) -> (Void# -> r) -> r
ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR = AccelerationStructureTypeKHR 0
-- | 'ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR' is a bottom-level
-- acceleration structure containing the AABBs or geometry to be
-- intersected.
pattern $bACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR :: AccelerationStructureTypeKHR
$mACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR :: forall r.
AccelerationStructureTypeKHR -> (Void# -> r) -> (Void# -> r) -> r
ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR = AccelerationStructureTypeKHR 1
{-# complete ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR,
             ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR :: AccelerationStructureTypeKHR #-}

instance Show AccelerationStructureTypeKHR where
  showsPrec :: Int -> AccelerationStructureTypeKHR -> ShowS
showsPrec p :: Int
p = \case
    ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR -> String -> ShowS
showString "ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR"
    ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR -> String -> ShowS
showString "ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR"
    AccelerationStructureTypeKHR x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "AccelerationStructureTypeKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read AccelerationStructureTypeKHR where
  readPrec :: ReadPrec AccelerationStructureTypeKHR
readPrec = ReadPrec AccelerationStructureTypeKHR
-> ReadPrec AccelerationStructureTypeKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec AccelerationStructureTypeKHR)]
-> ReadPrec AccelerationStructureTypeKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR", AccelerationStructureTypeKHR
-> ReadPrec AccelerationStructureTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure AccelerationStructureTypeKHR
ACCELERATION_STRUCTURE_TYPE_TOP_LEVEL_KHR)
                            , ("ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR", AccelerationStructureTypeKHR
-> ReadPrec AccelerationStructureTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure AccelerationStructureTypeKHR
ACCELERATION_STRUCTURE_TYPE_BOTTOM_LEVEL_KHR)]
                     ReadPrec AccelerationStructureTypeKHR
-> ReadPrec AccelerationStructureTypeKHR
-> ReadPrec AccelerationStructureTypeKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec AccelerationStructureTypeKHR
-> ReadPrec AccelerationStructureTypeKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "AccelerationStructureTypeKHR")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       AccelerationStructureTypeKHR
-> ReadPrec AccelerationStructureTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> AccelerationStructureTypeKHR
AccelerationStructureTypeKHR Int32
v)))


-- | VkGeometryTypeKHR - Enum specifying which type of geometry is provided
--
-- = See Also
--
-- 'AccelerationStructureCreateGeometryTypeInfoKHR',
-- 'AccelerationStructureGeometryKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.GeometryNV'
newtype GeometryTypeKHR = GeometryTypeKHR Int32
  deriving newtype (GeometryTypeKHR -> GeometryTypeKHR -> Bool
(GeometryTypeKHR -> GeometryTypeKHR -> Bool)
-> (GeometryTypeKHR -> GeometryTypeKHR -> Bool)
-> Eq GeometryTypeKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
$c/= :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
== :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
$c== :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
Eq, Eq GeometryTypeKHR
Eq GeometryTypeKHR =>
(GeometryTypeKHR -> GeometryTypeKHR -> Ordering)
-> (GeometryTypeKHR -> GeometryTypeKHR -> Bool)
-> (GeometryTypeKHR -> GeometryTypeKHR -> Bool)
-> (GeometryTypeKHR -> GeometryTypeKHR -> Bool)
-> (GeometryTypeKHR -> GeometryTypeKHR -> Bool)
-> (GeometryTypeKHR -> GeometryTypeKHR -> GeometryTypeKHR)
-> (GeometryTypeKHR -> GeometryTypeKHR -> GeometryTypeKHR)
-> Ord GeometryTypeKHR
GeometryTypeKHR -> GeometryTypeKHR -> Bool
GeometryTypeKHR -> GeometryTypeKHR -> Ordering
GeometryTypeKHR -> GeometryTypeKHR -> GeometryTypeKHR
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 :: GeometryTypeKHR -> GeometryTypeKHR -> GeometryTypeKHR
$cmin :: GeometryTypeKHR -> GeometryTypeKHR -> GeometryTypeKHR
max :: GeometryTypeKHR -> GeometryTypeKHR -> GeometryTypeKHR
$cmax :: GeometryTypeKHR -> GeometryTypeKHR -> GeometryTypeKHR
>= :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
$c>= :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
> :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
$c> :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
<= :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
$c<= :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
< :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
$c< :: GeometryTypeKHR -> GeometryTypeKHR -> Bool
compare :: GeometryTypeKHR -> GeometryTypeKHR -> Ordering
$ccompare :: GeometryTypeKHR -> GeometryTypeKHR -> Ordering
$cp1Ord :: Eq GeometryTypeKHR
Ord, Ptr b -> Int -> IO GeometryTypeKHR
Ptr b -> Int -> GeometryTypeKHR -> IO ()
Ptr GeometryTypeKHR -> IO GeometryTypeKHR
Ptr GeometryTypeKHR -> Int -> IO GeometryTypeKHR
Ptr GeometryTypeKHR -> Int -> GeometryTypeKHR -> IO ()
Ptr GeometryTypeKHR -> GeometryTypeKHR -> IO ()
GeometryTypeKHR -> Int
(GeometryTypeKHR -> Int)
-> (GeometryTypeKHR -> Int)
-> (Ptr GeometryTypeKHR -> Int -> IO GeometryTypeKHR)
-> (Ptr GeometryTypeKHR -> Int -> GeometryTypeKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO GeometryTypeKHR)
-> (forall b. Ptr b -> Int -> GeometryTypeKHR -> IO ())
-> (Ptr GeometryTypeKHR -> IO GeometryTypeKHR)
-> (Ptr GeometryTypeKHR -> GeometryTypeKHR -> IO ())
-> Storable GeometryTypeKHR
forall b. Ptr b -> Int -> IO GeometryTypeKHR
forall b. Ptr b -> Int -> GeometryTypeKHR -> 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 GeometryTypeKHR -> GeometryTypeKHR -> IO ()
$cpoke :: Ptr GeometryTypeKHR -> GeometryTypeKHR -> IO ()
peek :: Ptr GeometryTypeKHR -> IO GeometryTypeKHR
$cpeek :: Ptr GeometryTypeKHR -> IO GeometryTypeKHR
pokeByteOff :: Ptr b -> Int -> GeometryTypeKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> GeometryTypeKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO GeometryTypeKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO GeometryTypeKHR
pokeElemOff :: Ptr GeometryTypeKHR -> Int -> GeometryTypeKHR -> IO ()
$cpokeElemOff :: Ptr GeometryTypeKHR -> Int -> GeometryTypeKHR -> IO ()
peekElemOff :: Ptr GeometryTypeKHR -> Int -> IO GeometryTypeKHR
$cpeekElemOff :: Ptr GeometryTypeKHR -> Int -> IO GeometryTypeKHR
alignment :: GeometryTypeKHR -> Int
$calignment :: GeometryTypeKHR -> Int
sizeOf :: GeometryTypeKHR -> Int
$csizeOf :: GeometryTypeKHR -> Int
Storable, GeometryTypeKHR
GeometryTypeKHR -> Zero GeometryTypeKHR
forall a. a -> Zero a
zero :: GeometryTypeKHR
$czero :: GeometryTypeKHR
Zero)

-- | 'GEOMETRY_TYPE_TRIANGLES_KHR' specifies a geometry type consisting of
-- triangles.
pattern $bGEOMETRY_TYPE_TRIANGLES_KHR :: GeometryTypeKHR
$mGEOMETRY_TYPE_TRIANGLES_KHR :: forall r. GeometryTypeKHR -> (Void# -> r) -> (Void# -> r) -> r
GEOMETRY_TYPE_TRIANGLES_KHR = GeometryTypeKHR 0
-- | 'GEOMETRY_TYPE_AABBS_KHR' specifies a geometry type consisting of
-- axis-aligned bounding boxes.
pattern $bGEOMETRY_TYPE_AABBS_KHR :: GeometryTypeKHR
$mGEOMETRY_TYPE_AABBS_KHR :: forall r. GeometryTypeKHR -> (Void# -> r) -> (Void# -> r) -> r
GEOMETRY_TYPE_AABBS_KHR = GeometryTypeKHR 1
-- | 'GEOMETRY_TYPE_INSTANCES_KHR' specifies a geometry type consisting of
-- acceleration structure instances.
pattern $bGEOMETRY_TYPE_INSTANCES_KHR :: GeometryTypeKHR
$mGEOMETRY_TYPE_INSTANCES_KHR :: forall r. GeometryTypeKHR -> (Void# -> r) -> (Void# -> r) -> r
GEOMETRY_TYPE_INSTANCES_KHR = GeometryTypeKHR 1000150000
{-# complete GEOMETRY_TYPE_TRIANGLES_KHR,
             GEOMETRY_TYPE_AABBS_KHR,
             GEOMETRY_TYPE_INSTANCES_KHR :: GeometryTypeKHR #-}

instance Show GeometryTypeKHR where
  showsPrec :: Int -> GeometryTypeKHR -> ShowS
showsPrec p :: Int
p = \case
    GEOMETRY_TYPE_TRIANGLES_KHR -> String -> ShowS
showString "GEOMETRY_TYPE_TRIANGLES_KHR"
    GEOMETRY_TYPE_AABBS_KHR -> String -> ShowS
showString "GEOMETRY_TYPE_AABBS_KHR"
    GEOMETRY_TYPE_INSTANCES_KHR -> String -> ShowS
showString "GEOMETRY_TYPE_INSTANCES_KHR"
    GeometryTypeKHR x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "GeometryTypeKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read GeometryTypeKHR where
  readPrec :: ReadPrec GeometryTypeKHR
readPrec = ReadPrec GeometryTypeKHR -> ReadPrec GeometryTypeKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec GeometryTypeKHR)] -> ReadPrec GeometryTypeKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("GEOMETRY_TYPE_TRIANGLES_KHR", GeometryTypeKHR -> ReadPrec GeometryTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure GeometryTypeKHR
GEOMETRY_TYPE_TRIANGLES_KHR)
                            , ("GEOMETRY_TYPE_AABBS_KHR", GeometryTypeKHR -> ReadPrec GeometryTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure GeometryTypeKHR
GEOMETRY_TYPE_AABBS_KHR)
                            , ("GEOMETRY_TYPE_INSTANCES_KHR", GeometryTypeKHR -> ReadPrec GeometryTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure GeometryTypeKHR
GEOMETRY_TYPE_INSTANCES_KHR)]
                     ReadPrec GeometryTypeKHR
-> ReadPrec GeometryTypeKHR -> ReadPrec GeometryTypeKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int -> ReadPrec GeometryTypeKHR -> ReadPrec GeometryTypeKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "GeometryTypeKHR")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       GeometryTypeKHR -> ReadPrec GeometryTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> GeometryTypeKHR
GeometryTypeKHR Int32
v)))


-- | VkAccelerationStructureMemoryRequirementsTypeKHR - Acceleration
-- structure memory requirement type
--
-- = See Also
--
-- 'AccelerationStructureMemoryRequirementsInfoKHR'
newtype AccelerationStructureMemoryRequirementsTypeKHR = AccelerationStructureMemoryRequirementsTypeKHR Int32
  deriving newtype (AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
(AccelerationStructureMemoryRequirementsTypeKHR
 -> AccelerationStructureMemoryRequirementsTypeKHR -> Bool)
-> (AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR -> Bool)
-> Eq AccelerationStructureMemoryRequirementsTypeKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
$c/= :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
== :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
$c== :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
Eq, Eq AccelerationStructureMemoryRequirementsTypeKHR
Eq AccelerationStructureMemoryRequirementsTypeKHR =>
(AccelerationStructureMemoryRequirementsTypeKHR
 -> AccelerationStructureMemoryRequirementsTypeKHR -> Ordering)
-> (AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR -> Bool)
-> (AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR -> Bool)
-> (AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR -> Bool)
-> (AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR -> Bool)
-> (AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR)
-> (AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR)
-> Ord AccelerationStructureMemoryRequirementsTypeKHR
AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Ordering
AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
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 :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
$cmin :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
max :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
$cmax :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR
>= :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
$c>= :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
> :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
$c> :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
<= :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
$c<= :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
< :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
$c< :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Bool
compare :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Ordering
$ccompare :: AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> Ordering
$cp1Ord :: Eq AccelerationStructureMemoryRequirementsTypeKHR
Ord, Ptr b -> Int -> IO AccelerationStructureMemoryRequirementsTypeKHR
Ptr b
-> Int -> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> IO AccelerationStructureMemoryRequirementsTypeKHR
Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> Int -> IO AccelerationStructureMemoryRequirementsTypeKHR
Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> Int -> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
AccelerationStructureMemoryRequirementsTypeKHR -> Int
(AccelerationStructureMemoryRequirementsTypeKHR -> Int)
-> (AccelerationStructureMemoryRequirementsTypeKHR -> Int)
-> (Ptr AccelerationStructureMemoryRequirementsTypeKHR
    -> Int -> IO AccelerationStructureMemoryRequirementsTypeKHR)
-> (Ptr AccelerationStructureMemoryRequirementsTypeKHR
    -> Int -> AccelerationStructureMemoryRequirementsTypeKHR -> IO ())
-> (forall b.
    Ptr b -> Int -> IO AccelerationStructureMemoryRequirementsTypeKHR)
-> (forall b.
    Ptr b
    -> Int -> AccelerationStructureMemoryRequirementsTypeKHR -> IO ())
-> (Ptr AccelerationStructureMemoryRequirementsTypeKHR
    -> IO AccelerationStructureMemoryRequirementsTypeKHR)
-> (Ptr AccelerationStructureMemoryRequirementsTypeKHR
    -> AccelerationStructureMemoryRequirementsTypeKHR -> IO ())
-> Storable AccelerationStructureMemoryRequirementsTypeKHR
forall b.
Ptr b -> Int -> IO AccelerationStructureMemoryRequirementsTypeKHR
forall b.
Ptr b
-> Int -> AccelerationStructureMemoryRequirementsTypeKHR -> 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 AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
$cpoke :: Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
peek :: Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> IO AccelerationStructureMemoryRequirementsTypeKHR
$cpeek :: Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> IO AccelerationStructureMemoryRequirementsTypeKHR
pokeByteOff :: Ptr b
-> Int -> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
$cpokeByteOff :: forall b.
Ptr b
-> Int -> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO AccelerationStructureMemoryRequirementsTypeKHR
$cpeekByteOff :: forall b.
Ptr b -> Int -> IO AccelerationStructureMemoryRequirementsTypeKHR
pokeElemOff :: Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> Int -> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
$cpokeElemOff :: Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> Int -> AccelerationStructureMemoryRequirementsTypeKHR -> IO ()
peekElemOff :: Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> Int -> IO AccelerationStructureMemoryRequirementsTypeKHR
$cpeekElemOff :: Ptr AccelerationStructureMemoryRequirementsTypeKHR
-> Int -> IO AccelerationStructureMemoryRequirementsTypeKHR
alignment :: AccelerationStructureMemoryRequirementsTypeKHR -> Int
$calignment :: AccelerationStructureMemoryRequirementsTypeKHR -> Int
sizeOf :: AccelerationStructureMemoryRequirementsTypeKHR -> Int
$csizeOf :: AccelerationStructureMemoryRequirementsTypeKHR -> Int
Storable, AccelerationStructureMemoryRequirementsTypeKHR
AccelerationStructureMemoryRequirementsTypeKHR
-> Zero AccelerationStructureMemoryRequirementsTypeKHR
forall a. a -> Zero a
zero :: AccelerationStructureMemoryRequirementsTypeKHR
$czero :: AccelerationStructureMemoryRequirementsTypeKHR
Zero)

-- | 'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR' requests
-- the memory requirement for the
-- 'Vulkan.Extensions.Handles.AccelerationStructureKHR' backing store.
pattern $bACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR :: AccelerationStructureMemoryRequirementsTypeKHR
$mACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR :: forall r.
AccelerationStructureMemoryRequirementsTypeKHR
-> (Void# -> r) -> (Void# -> r) -> r
ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR = AccelerationStructureMemoryRequirementsTypeKHR 0
-- | 'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR'
-- requests the memory requirement for scratch space during the initial
-- build.
pattern $bACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR :: AccelerationStructureMemoryRequirementsTypeKHR
$mACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR :: forall r.
AccelerationStructureMemoryRequirementsTypeKHR
-> (Void# -> r) -> (Void# -> r) -> r
ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR = AccelerationStructureMemoryRequirementsTypeKHR 1
-- | 'ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR'
-- requests the memory requirement for scratch space during an update.
pattern $bACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR :: AccelerationStructureMemoryRequirementsTypeKHR
$mACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR :: forall r.
AccelerationStructureMemoryRequirementsTypeKHR
-> (Void# -> r) -> (Void# -> r) -> r
ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR = AccelerationStructureMemoryRequirementsTypeKHR 2
{-# complete ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR,
             ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR,
             ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR :: AccelerationStructureMemoryRequirementsTypeKHR #-}

instance Show AccelerationStructureMemoryRequirementsTypeKHR where
  showsPrec :: Int -> AccelerationStructureMemoryRequirementsTypeKHR -> ShowS
showsPrec p :: Int
p = \case
    ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR -> String -> ShowS
showString "ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR"
    ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR -> String -> ShowS
showString "ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR"
    ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR -> String -> ShowS
showString "ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR"
    AccelerationStructureMemoryRequirementsTypeKHR x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "AccelerationStructureMemoryRequirementsTypeKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read AccelerationStructureMemoryRequirementsTypeKHR where
  readPrec :: ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
readPrec = ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec AccelerationStructureMemoryRequirementsTypeKHR)]
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR", AccelerationStructureMemoryRequirementsTypeKHR
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure AccelerationStructureMemoryRequirementsTypeKHR
ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_OBJECT_KHR)
                            , ("ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR", AccelerationStructureMemoryRequirementsTypeKHR
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure AccelerationStructureMemoryRequirementsTypeKHR
ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_BUILD_SCRATCH_KHR)
                            , ("ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR", AccelerationStructureMemoryRequirementsTypeKHR
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure AccelerationStructureMemoryRequirementsTypeKHR
ACCELERATION_STRUCTURE_MEMORY_REQUIREMENTS_TYPE_UPDATE_SCRATCH_KHR)]
                     ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "AccelerationStructureMemoryRequirementsTypeKHR")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       AccelerationStructureMemoryRequirementsTypeKHR
-> ReadPrec AccelerationStructureMemoryRequirementsTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> AccelerationStructureMemoryRequirementsTypeKHR
AccelerationStructureMemoryRequirementsTypeKHR Int32
v)))


-- | VkAccelerationStructureBuildTypeKHR - Acceleration structure build type
--
-- = See Also
--
-- 'AccelerationStructureMemoryRequirementsInfoKHR'
newtype AccelerationStructureBuildTypeKHR = AccelerationStructureBuildTypeKHR Int32
  deriving newtype (AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
(AccelerationStructureBuildTypeKHR
 -> AccelerationStructureBuildTypeKHR -> Bool)
-> (AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR -> Bool)
-> Eq AccelerationStructureBuildTypeKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
$c/= :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
== :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
$c== :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
Eq, Eq AccelerationStructureBuildTypeKHR
Eq AccelerationStructureBuildTypeKHR =>
(AccelerationStructureBuildTypeKHR
 -> AccelerationStructureBuildTypeKHR -> Ordering)
-> (AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR -> Bool)
-> (AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR -> Bool)
-> (AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR -> Bool)
-> (AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR -> Bool)
-> (AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR)
-> (AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR)
-> Ord AccelerationStructureBuildTypeKHR
AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Ordering
AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
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 :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
$cmin :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
max :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
$cmax :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR
>= :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
$c>= :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
> :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
$c> :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
<= :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
$c<= :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
< :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
$c< :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Bool
compare :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Ordering
$ccompare :: AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> Ordering
$cp1Ord :: Eq AccelerationStructureBuildTypeKHR
Ord, Ptr b -> Int -> IO AccelerationStructureBuildTypeKHR
Ptr b -> Int -> AccelerationStructureBuildTypeKHR -> IO ()
Ptr AccelerationStructureBuildTypeKHR
-> IO AccelerationStructureBuildTypeKHR
Ptr AccelerationStructureBuildTypeKHR
-> Int -> IO AccelerationStructureBuildTypeKHR
Ptr AccelerationStructureBuildTypeKHR
-> Int -> AccelerationStructureBuildTypeKHR -> IO ()
Ptr AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> IO ()
AccelerationStructureBuildTypeKHR -> Int
(AccelerationStructureBuildTypeKHR -> Int)
-> (AccelerationStructureBuildTypeKHR -> Int)
-> (Ptr AccelerationStructureBuildTypeKHR
    -> Int -> IO AccelerationStructureBuildTypeKHR)
-> (Ptr AccelerationStructureBuildTypeKHR
    -> Int -> AccelerationStructureBuildTypeKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO AccelerationStructureBuildTypeKHR)
-> (forall b.
    Ptr b -> Int -> AccelerationStructureBuildTypeKHR -> IO ())
-> (Ptr AccelerationStructureBuildTypeKHR
    -> IO AccelerationStructureBuildTypeKHR)
-> (Ptr AccelerationStructureBuildTypeKHR
    -> AccelerationStructureBuildTypeKHR -> IO ())
-> Storable AccelerationStructureBuildTypeKHR
forall b. Ptr b -> Int -> IO AccelerationStructureBuildTypeKHR
forall b.
Ptr b -> Int -> AccelerationStructureBuildTypeKHR -> 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 AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> IO ()
$cpoke :: Ptr AccelerationStructureBuildTypeKHR
-> AccelerationStructureBuildTypeKHR -> IO ()
peek :: Ptr AccelerationStructureBuildTypeKHR
-> IO AccelerationStructureBuildTypeKHR
$cpeek :: Ptr AccelerationStructureBuildTypeKHR
-> IO AccelerationStructureBuildTypeKHR
pokeByteOff :: Ptr b -> Int -> AccelerationStructureBuildTypeKHR -> IO ()
$cpokeByteOff :: forall b.
Ptr b -> Int -> AccelerationStructureBuildTypeKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO AccelerationStructureBuildTypeKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AccelerationStructureBuildTypeKHR
pokeElemOff :: Ptr AccelerationStructureBuildTypeKHR
-> Int -> AccelerationStructureBuildTypeKHR -> IO ()
$cpokeElemOff :: Ptr AccelerationStructureBuildTypeKHR
-> Int -> AccelerationStructureBuildTypeKHR -> IO ()
peekElemOff :: Ptr AccelerationStructureBuildTypeKHR
-> Int -> IO AccelerationStructureBuildTypeKHR
$cpeekElemOff :: Ptr AccelerationStructureBuildTypeKHR
-> Int -> IO AccelerationStructureBuildTypeKHR
alignment :: AccelerationStructureBuildTypeKHR -> Int
$calignment :: AccelerationStructureBuildTypeKHR -> Int
sizeOf :: AccelerationStructureBuildTypeKHR -> Int
$csizeOf :: AccelerationStructureBuildTypeKHR -> Int
Storable, AccelerationStructureBuildTypeKHR
AccelerationStructureBuildTypeKHR
-> Zero AccelerationStructureBuildTypeKHR
forall a. a -> Zero a
zero :: AccelerationStructureBuildTypeKHR
$czero :: AccelerationStructureBuildTypeKHR
Zero)

-- | 'ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR' requests the memory
-- requirement for operations performed by the host.
pattern $bACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR :: AccelerationStructureBuildTypeKHR
$mACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR :: forall r.
AccelerationStructureBuildTypeKHR
-> (Void# -> r) -> (Void# -> r) -> r
ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR = AccelerationStructureBuildTypeKHR 0
-- | 'ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR' requests the memory
-- requirement for operations performed by the device.
pattern $bACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR :: AccelerationStructureBuildTypeKHR
$mACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR :: forall r.
AccelerationStructureBuildTypeKHR
-> (Void# -> r) -> (Void# -> r) -> r
ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR = AccelerationStructureBuildTypeKHR 1
-- | 'ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR' requests the
-- memory requirement for operations performed by either the host, or the
-- device.
pattern $bACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR :: AccelerationStructureBuildTypeKHR
$mACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR :: forall r.
AccelerationStructureBuildTypeKHR
-> (Void# -> r) -> (Void# -> r) -> r
ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR = AccelerationStructureBuildTypeKHR 2
{-# complete ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR,
             ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR,
             ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR :: AccelerationStructureBuildTypeKHR #-}

instance Show AccelerationStructureBuildTypeKHR where
  showsPrec :: Int -> AccelerationStructureBuildTypeKHR -> ShowS
showsPrec p :: Int
p = \case
    ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR -> String -> ShowS
showString "ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR"
    ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR -> String -> ShowS
showString "ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR"
    ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR -> String -> ShowS
showString "ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR"
    AccelerationStructureBuildTypeKHR x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "AccelerationStructureBuildTypeKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read AccelerationStructureBuildTypeKHR where
  readPrec :: ReadPrec AccelerationStructureBuildTypeKHR
readPrec = ReadPrec AccelerationStructureBuildTypeKHR
-> ReadPrec AccelerationStructureBuildTypeKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec AccelerationStructureBuildTypeKHR)]
-> ReadPrec AccelerationStructureBuildTypeKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR", AccelerationStructureBuildTypeKHR
-> ReadPrec AccelerationStructureBuildTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure AccelerationStructureBuildTypeKHR
ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_KHR)
                            , ("ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR", AccelerationStructureBuildTypeKHR
-> ReadPrec AccelerationStructureBuildTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure AccelerationStructureBuildTypeKHR
ACCELERATION_STRUCTURE_BUILD_TYPE_DEVICE_KHR)
                            , ("ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR", AccelerationStructureBuildTypeKHR
-> ReadPrec AccelerationStructureBuildTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure AccelerationStructureBuildTypeKHR
ACCELERATION_STRUCTURE_BUILD_TYPE_HOST_OR_DEVICE_KHR)]
                     ReadPrec AccelerationStructureBuildTypeKHR
-> ReadPrec AccelerationStructureBuildTypeKHR
-> ReadPrec AccelerationStructureBuildTypeKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec AccelerationStructureBuildTypeKHR
-> ReadPrec AccelerationStructureBuildTypeKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "AccelerationStructureBuildTypeKHR")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       AccelerationStructureBuildTypeKHR
-> ReadPrec AccelerationStructureBuildTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> AccelerationStructureBuildTypeKHR
AccelerationStructureBuildTypeKHR Int32
v)))


-- | VkRayTracingShaderGroupTypeKHR - Shader group types
--
-- = Description
--
-- Note
--
-- For current group types, the hit group type could be inferred from the
-- presence or absence of the intersection shader, but we provide the type
-- explicitly for future hit groups that do not have that property.
--
-- = See Also
--
-- 'RayTracingShaderGroupCreateInfoKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.RayTracingShaderGroupCreateInfoNV'
newtype RayTracingShaderGroupTypeKHR = RayTracingShaderGroupTypeKHR Int32
  deriving newtype (RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
(RayTracingShaderGroupTypeKHR
 -> RayTracingShaderGroupTypeKHR -> Bool)
-> (RayTracingShaderGroupTypeKHR
    -> RayTracingShaderGroupTypeKHR -> Bool)
-> Eq RayTracingShaderGroupTypeKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
$c/= :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
== :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
$c== :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
Eq, Eq RayTracingShaderGroupTypeKHR
Eq RayTracingShaderGroupTypeKHR =>
(RayTracingShaderGroupTypeKHR
 -> RayTracingShaderGroupTypeKHR -> Ordering)
-> (RayTracingShaderGroupTypeKHR
    -> RayTracingShaderGroupTypeKHR -> Bool)
-> (RayTracingShaderGroupTypeKHR
    -> RayTracingShaderGroupTypeKHR -> Bool)
-> (RayTracingShaderGroupTypeKHR
    -> RayTracingShaderGroupTypeKHR -> Bool)
-> (RayTracingShaderGroupTypeKHR
    -> RayTracingShaderGroupTypeKHR -> Bool)
-> (RayTracingShaderGroupTypeKHR
    -> RayTracingShaderGroupTypeKHR -> RayTracingShaderGroupTypeKHR)
-> (RayTracingShaderGroupTypeKHR
    -> RayTracingShaderGroupTypeKHR -> RayTracingShaderGroupTypeKHR)
-> Ord RayTracingShaderGroupTypeKHR
RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Ordering
RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> RayTracingShaderGroupTypeKHR
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 :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> RayTracingShaderGroupTypeKHR
$cmin :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> RayTracingShaderGroupTypeKHR
max :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> RayTracingShaderGroupTypeKHR
$cmax :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> RayTracingShaderGroupTypeKHR
>= :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
$c>= :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
> :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
$c> :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
<= :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
$c<= :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
< :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
$c< :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Bool
compare :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Ordering
$ccompare :: RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> Ordering
$cp1Ord :: Eq RayTracingShaderGroupTypeKHR
Ord, Ptr b -> Int -> IO RayTracingShaderGroupTypeKHR
Ptr b -> Int -> RayTracingShaderGroupTypeKHR -> IO ()
Ptr RayTracingShaderGroupTypeKHR -> IO RayTracingShaderGroupTypeKHR
Ptr RayTracingShaderGroupTypeKHR
-> Int -> IO RayTracingShaderGroupTypeKHR
Ptr RayTracingShaderGroupTypeKHR
-> Int -> RayTracingShaderGroupTypeKHR -> IO ()
Ptr RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> IO ()
RayTracingShaderGroupTypeKHR -> Int
(RayTracingShaderGroupTypeKHR -> Int)
-> (RayTracingShaderGroupTypeKHR -> Int)
-> (Ptr RayTracingShaderGroupTypeKHR
    -> Int -> IO RayTracingShaderGroupTypeKHR)
-> (Ptr RayTracingShaderGroupTypeKHR
    -> Int -> RayTracingShaderGroupTypeKHR -> IO ())
-> (forall b. Ptr b -> Int -> IO RayTracingShaderGroupTypeKHR)
-> (forall b.
    Ptr b -> Int -> RayTracingShaderGroupTypeKHR -> IO ())
-> (Ptr RayTracingShaderGroupTypeKHR
    -> IO RayTracingShaderGroupTypeKHR)
-> (Ptr RayTracingShaderGroupTypeKHR
    -> RayTracingShaderGroupTypeKHR -> IO ())
-> Storable RayTracingShaderGroupTypeKHR
forall b. Ptr b -> Int -> IO RayTracingShaderGroupTypeKHR
forall b. Ptr b -> Int -> RayTracingShaderGroupTypeKHR -> 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 RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> IO ()
$cpoke :: Ptr RayTracingShaderGroupTypeKHR
-> RayTracingShaderGroupTypeKHR -> IO ()
peek :: Ptr RayTracingShaderGroupTypeKHR -> IO RayTracingShaderGroupTypeKHR
$cpeek :: Ptr RayTracingShaderGroupTypeKHR -> IO RayTracingShaderGroupTypeKHR
pokeByteOff :: Ptr b -> Int -> RayTracingShaderGroupTypeKHR -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> RayTracingShaderGroupTypeKHR -> IO ()
peekByteOff :: Ptr b -> Int -> IO RayTracingShaderGroupTypeKHR
$cpeekByteOff :: forall b. Ptr b -> Int -> IO RayTracingShaderGroupTypeKHR
pokeElemOff :: Ptr RayTracingShaderGroupTypeKHR
-> Int -> RayTracingShaderGroupTypeKHR -> IO ()
$cpokeElemOff :: Ptr RayTracingShaderGroupTypeKHR
-> Int -> RayTracingShaderGroupTypeKHR -> IO ()
peekElemOff :: Ptr RayTracingShaderGroupTypeKHR
-> Int -> IO RayTracingShaderGroupTypeKHR
$cpeekElemOff :: Ptr RayTracingShaderGroupTypeKHR
-> Int -> IO RayTracingShaderGroupTypeKHR
alignment :: RayTracingShaderGroupTypeKHR -> Int
$calignment :: RayTracingShaderGroupTypeKHR -> Int
sizeOf :: RayTracingShaderGroupTypeKHR -> Int
$csizeOf :: RayTracingShaderGroupTypeKHR -> Int
Storable, RayTracingShaderGroupTypeKHR
RayTracingShaderGroupTypeKHR -> Zero RayTracingShaderGroupTypeKHR
forall a. a -> Zero a
zero :: RayTracingShaderGroupTypeKHR
$czero :: RayTracingShaderGroupTypeKHR
Zero)

-- | 'RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR' indicates a shader group
-- with a single
-- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_RAYGEN_BIT_KHR',
-- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_MISS_BIT_KHR', or
-- 'Vulkan.Core10.Enums.ShaderStageFlagBits.SHADER_STAGE_CALLABLE_BIT_KHR'
-- shader in it.
pattern $bRAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR :: RayTracingShaderGroupTypeKHR
$mRAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR :: forall r.
RayTracingShaderGroupTypeKHR -> (Void# -> r) -> (Void# -> r) -> r
RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR = RayTracingShaderGroupTypeKHR 0
-- | 'RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR' specifies a
-- shader group that only hits triangles and /must/ not contain an
-- intersection shader, only closest hit and any-hit shaders.
pattern $bRAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR :: RayTracingShaderGroupTypeKHR
$mRAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR :: forall r.
RayTracingShaderGroupTypeKHR -> (Void# -> r) -> (Void# -> r) -> r
RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR = RayTracingShaderGroupTypeKHR 1
-- | 'RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR' specifies a
-- shader group that only intersects with custom geometry and /must/
-- contain an intersection shader and /may/ contain closest hit and any-hit
-- shaders.
pattern $bRAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR :: RayTracingShaderGroupTypeKHR
$mRAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR :: forall r.
RayTracingShaderGroupTypeKHR -> (Void# -> r) -> (Void# -> r) -> r
RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR = RayTracingShaderGroupTypeKHR 2
{-# complete RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR,
             RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR,
             RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR :: RayTracingShaderGroupTypeKHR #-}

instance Show RayTracingShaderGroupTypeKHR where
  showsPrec :: Int -> RayTracingShaderGroupTypeKHR -> ShowS
showsPrec p :: Int
p = \case
    RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR -> String -> ShowS
showString "RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR"
    RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR -> String -> ShowS
showString "RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR"
    RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR -> String -> ShowS
showString "RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR"
    RayTracingShaderGroupTypeKHR x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "RayTracingShaderGroupTypeKHR " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)

instance Read RayTracingShaderGroupTypeKHR where
  readPrec :: ReadPrec RayTracingShaderGroupTypeKHR
readPrec = ReadPrec RayTracingShaderGroupTypeKHR
-> ReadPrec RayTracingShaderGroupTypeKHR
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec RayTracingShaderGroupTypeKHR)]
-> ReadPrec RayTracingShaderGroupTypeKHR
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR", RayTracingShaderGroupTypeKHR
-> ReadPrec RayTracingShaderGroupTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure RayTracingShaderGroupTypeKHR
RAY_TRACING_SHADER_GROUP_TYPE_GENERAL_KHR)
                            , ("RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR", RayTracingShaderGroupTypeKHR
-> ReadPrec RayTracingShaderGroupTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure RayTracingShaderGroupTypeKHR
RAY_TRACING_SHADER_GROUP_TYPE_TRIANGLES_HIT_GROUP_KHR)
                            , ("RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR", RayTracingShaderGroupTypeKHR
-> ReadPrec RayTracingShaderGroupTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure RayTracingShaderGroupTypeKHR
RAY_TRACING_SHADER_GROUP_TYPE_PROCEDURAL_HIT_GROUP_KHR)]
                     ReadPrec RayTracingShaderGroupTypeKHR
-> ReadPrec RayTracingShaderGroupTypeKHR
-> ReadPrec RayTracingShaderGroupTypeKHR
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
                     Int
-> ReadPrec RayTracingShaderGroupTypeKHR
-> ReadPrec RayTracingShaderGroupTypeKHR
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
                       Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "RayTracingShaderGroupTypeKHR")
                       Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
                       RayTracingShaderGroupTypeKHR
-> ReadPrec RayTracingShaderGroupTypeKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> RayTracingShaderGroupTypeKHR
RayTracingShaderGroupTypeKHR Int32
v)))


type KHR_RAY_TRACING_SPEC_VERSION = 8

-- No documentation found for TopLevel "VK_KHR_RAY_TRACING_SPEC_VERSION"
pattern KHR_RAY_TRACING_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_RAY_TRACING_SPEC_VERSION :: a
$mKHR_RAY_TRACING_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
KHR_RAY_TRACING_SPEC_VERSION = 8


type KHR_RAY_TRACING_EXTENSION_NAME = "VK_KHR_ray_tracing"

-- No documentation found for TopLevel "VK_KHR_RAY_TRACING_EXTENSION_NAME"
pattern KHR_RAY_TRACING_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_RAY_TRACING_EXTENSION_NAME :: a
$mKHR_RAY_TRACING_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
KHR_RAY_TRACING_EXTENSION_NAME = "VK_KHR_ray_tracing"