{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_push_descriptor  ( cmdPushDescriptorSetKHR
                                                 , cmdPushDescriptorSetWithTemplateKHR
                                                 , PhysicalDevicePushDescriptorPropertiesKHR(..)
                                                 , KHR_PUSH_DESCRIPTOR_SPEC_VERSION
                                                 , pattern KHR_PUSH_DESCRIPTOR_SPEC_VERSION
                                                 , KHR_PUSH_DESCRIPTOR_EXTENSION_NAME
                                                 , pattern KHR_PUSH_DESCRIPTOR_EXTENSION_NAME
                                                 ) where

import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import GHC.IO (throwIO)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
import Data.String (IsString)
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.Handles (CommandBuffer)
import Vulkan.Core10.Handles (CommandBuffer(..))
import Vulkan.Core10.Handles (CommandBuffer_T)
import Vulkan.Core11.Handles (DescriptorUpdateTemplate)
import Vulkan.Core11.Handles (DescriptorUpdateTemplate(..))
import Vulkan.Dynamic (DeviceCmds(pVkCmdPushDescriptorSetKHR))
import Vulkan.Dynamic (DeviceCmds(pVkCmdPushDescriptorSetWithTemplateKHR))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint)
import Vulkan.Core10.Enums.PipelineBindPoint (PipelineBindPoint(..))
import Vulkan.Core10.Handles (PipelineLayout)
import Vulkan.Core10.Handles (PipelineLayout(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Core10.DescriptorSet (WriteDescriptorSet)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PHYSICAL_DEVICE_PUSH_DESCRIPTOR_PROPERTIES_KHR))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCmdPushDescriptorSetKHR
  :: FunPtr (Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr (SomeStruct WriteDescriptorSet) -> IO ()) -> Ptr CommandBuffer_T -> PipelineBindPoint -> PipelineLayout -> Word32 -> Word32 -> Ptr (SomeStruct WriteDescriptorSet) -> IO ()

-- | vkCmdPushDescriptorSetKHR - Pushes descriptor updates into a command
-- buffer
--
-- = Description
--
-- /Push descriptors/ are a small bank of descriptors whose storage is
-- internally managed by the command buffer rather than being written into
-- a descriptor set and later bound to a command buffer. Push descriptors
-- allow for incremental updates of descriptors without managing the
-- lifetime of descriptor sets.
--
-- When a command buffer begins recording, all push descriptors are
-- undefined. Push descriptors /can/ be updated incrementally and cause
-- shaders to use the updated descriptors for subsequent
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipeline-bindpoint-commands bound pipeline commands>
-- with the pipeline type set by @pipelineBindPoint@ until the descriptor
-- is overwritten, or else until the set is disturbed as described in
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#descriptorsets-compatibility Pipeline Layout Compatibility>.
-- When the set is disturbed or push descriptors with a different
-- descriptor set layout are set, all push descriptors are undefined.
--
-- Push descriptors that are
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#shaders-staticuse statically used>
-- by a pipeline /must/ not be undefined at the time that a draw or
-- dispatch command is recorded to execute using that pipeline. This
-- includes immutable sampler descriptors, which /must/ be pushed before
-- they are accessed by a pipeline (the immutable samplers are pushed,
-- rather than the samplers in @pDescriptorWrites@). Push descriptors that
-- are not statically used /can/ remain undefined.
--
-- Push descriptors do not use dynamic offsets. Instead, the corresponding
-- non-dynamic descriptor types /can/ be used and the @offset@ member of
-- 'Vulkan.Core10.DescriptorSet.DescriptorBufferInfo' /can/ be changed each
-- time the descriptor is written.
--
-- Each element of @pDescriptorWrites@ is interpreted as in
-- 'Vulkan.Core10.DescriptorSet.WriteDescriptorSet', except the @dstSet@
-- member is ignored.
--
-- To push an immutable sampler, use a
-- 'Vulkan.Core10.DescriptorSet.WriteDescriptorSet' with @dstBinding@ and
-- @dstArrayElement@ selecting the immutable sampler’s binding. If the
-- descriptor type is
-- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_SAMPLER', the
-- @pImageInfo@ parameter is ignored and the immutable sampler is taken
-- from the push descriptor set layout in the pipeline layout. If the
-- descriptor type is
-- 'Vulkan.Core10.Enums.DescriptorType.DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER',
-- the @sampler@ member of the @pImageInfo@ parameter is ignored and the
-- immutable sampler is taken from the push descriptor set layout in the
-- pipeline layout.
--
-- == Valid Usage
--
-- -   @pipelineBindPoint@ /must/ be supported by the @commandBuffer@’s
--     parent 'Vulkan.Core10.Handles.CommandPool'’s queue family
--
-- -   @set@ /must/ be less than
--     'Vulkan.Core10.PipelineLayout.PipelineLayoutCreateInfo'::@setLayoutCount@
--     provided when @layout@ was created
--
-- -   @set@ /must/ be the unique set number in the pipeline layout that
--     uses a descriptor set layout that was created with
--     'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR'
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @pipelineBindPoint@ /must/ be a valid
--     'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' value
--
-- -   @layout@ /must/ be a valid 'Vulkan.Core10.Handles.PipelineLayout'
--     handle
--
-- -   @pDescriptorWrites@ /must/ be a valid pointer to an array of
--     @descriptorWriteCount@ valid
--     'Vulkan.Core10.DescriptorSet.WriteDescriptorSet' 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 graphics, or compute operations
--
-- -   @descriptorWriteCount@ /must/ be greater than @0@
--
-- -   Both of @commandBuffer@, and @layout@ /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                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint',
-- 'Vulkan.Core10.Handles.PipelineLayout',
-- 'Vulkan.Core10.DescriptorSet.WriteDescriptorSet'
cmdPushDescriptorSetKHR :: forall io
                         . (MonadIO io)
                        => -- | @commandBuffer@ is the command buffer that the descriptors will be
                           -- recorded in.
                           CommandBuffer
                        -> -- | @pipelineBindPoint@ is a
                           -- 'Vulkan.Core10.Enums.PipelineBindPoint.PipelineBindPoint' indicating the
                           -- type of the pipeline that will use the descriptors. There is a separate
                           -- set of push descriptor bindings for each pipeline type, so binding one
                           -- does not disturb the others.
                           PipelineBindPoint
                        -> -- | @layout@ is a 'Vulkan.Core10.Handles.PipelineLayout' object used to
                           -- program the bindings.
                           PipelineLayout
                        -> -- | @set@ is the set number of the descriptor set in the pipeline layout
                           -- that will be updated.
                           ("set" ::: Word32)
                        -> -- | @pDescriptorWrites@ is a pointer to an array of
                           -- 'Vulkan.Core10.DescriptorSet.WriteDescriptorSet' structures describing
                           -- the descriptors to be updated.
                           ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
                        -> io ()
cmdPushDescriptorSetKHR :: CommandBuffer
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> io ()
cmdPushDescriptorSetKHR commandBuffer :: CommandBuffer
commandBuffer pipelineBindPoint :: PipelineBindPoint
pipelineBindPoint layout :: PipelineLayout
layout set :: "set" ::: Word32
set descriptorWrites :: "descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)
descriptorWrites = 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 vkCmdPushDescriptorSetKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("set" ::: Word32)
   -> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
   -> IO ())
vkCmdPushDescriptorSetKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> PipelineBindPoint
      -> PipelineLayout
      -> ("set" ::: Word32)
      -> ("set" ::: Word32)
      -> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
      -> IO ())
pVkCmdPushDescriptorSetKHR (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
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("set" ::: Word32)
   -> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
   -> IO ())
vkCmdPushDescriptorSetKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("set" ::: Word32)
   -> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> PipelineBindPoint
      -> PipelineLayout
      -> ("set" ::: Word32)
      -> ("set" ::: Word32)
      -> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("set" ::: Word32)
   -> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
   -> 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 vkCmdPushDescriptorSetKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdPushDescriptorSetKHR' :: Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
-> IO ()
vkCmdPushDescriptorSetKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("set" ::: Word32)
   -> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
   -> IO ())
-> Ptr CommandBuffer_T
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
-> IO ()
mkVkCmdPushDescriptorSetKHR FunPtr
  (Ptr CommandBuffer_T
   -> PipelineBindPoint
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("set" ::: Word32)
   -> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
   -> IO ())
vkCmdPushDescriptorSetKHRPtr
  Ptr (WriteDescriptorSet Any)
pPDescriptorWrites <- ((Ptr (WriteDescriptorSet Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (WriteDescriptorSet Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (WriteDescriptorSet Any) -> IO ()) -> IO ())
 -> ContT () IO (Ptr (WriteDescriptorSet Any)))
-> ((Ptr (WriteDescriptorSet Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (WriteDescriptorSet Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (WriteDescriptorSet Any) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(WriteDescriptorSet _) ((("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)
descriptorWrites)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 64) 8
  (Int -> SomeStruct WriteDescriptorSet -> ContT () IO ())
-> ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct WriteDescriptorSet
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
$ ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
-> SomeStruct WriteDescriptorSet -> 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 (WriteDescriptorSet Any)
-> "pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (WriteDescriptorSet Any)
pPDescriptorWrites Ptr (WriteDescriptorSet Any) -> Int -> Ptr (WriteDescriptorSet _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (64 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (WriteDescriptorSet _))) (SomeStruct WriteDescriptorSet
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
$ ())) ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)
descriptorWrites)
  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
-> PipelineBindPoint
-> PipelineLayout
-> ("set" ::: Word32)
-> ("set" ::: Word32)
-> ("pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet))
-> IO ()
vkCmdPushDescriptorSetKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (PipelineBindPoint
pipelineBindPoint) (PipelineLayout
layout) ("set" ::: Word32
set) ((Int -> "set" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
 -> Int)
-> ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet))
-> Int
forall a b. (a -> b) -> a -> b
$ ("descriptorWrites" ::: Vector (SomeStruct WriteDescriptorSet)
descriptorWrites)) :: Word32)) (Ptr (WriteDescriptorSet Any)
-> "pDescriptorWrites" ::: Ptr (SomeStruct WriteDescriptorSet)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (WriteDescriptorSet Any)
pPDescriptorWrites))
  () -> 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" mkVkCmdPushDescriptorSetWithTemplateKHR
  :: FunPtr (Ptr CommandBuffer_T -> DescriptorUpdateTemplate -> PipelineLayout -> Word32 -> Ptr () -> IO ()) -> Ptr CommandBuffer_T -> DescriptorUpdateTemplate -> PipelineLayout -> Word32 -> Ptr () -> IO ()

-- | vkCmdPushDescriptorSetWithTemplateKHR - Pushes descriptor updates into a
-- command buffer using a descriptor update template
--
-- == Valid Usage
--
-- -   The @pipelineBindPoint@ specified during the creation of the
--     descriptor update template /must/ be supported by the
--     @commandBuffer@’s parent 'Vulkan.Core10.Handles.CommandPool'’s queue
--     family
--
-- -   @pData@ /must/ be a valid pointer to a memory containing one or more
--     valid instances of
--     'Vulkan.Core10.DescriptorSet.DescriptorImageInfo',
--     'Vulkan.Core10.DescriptorSet.DescriptorBufferInfo', or
--     'Vulkan.Core10.Handles.BufferView' in a layout defined by
--     @descriptorUpdateTemplate@ when it was created with
--     'Vulkan.Extensions.VK_KHR_descriptor_update_template.createDescriptorUpdateTemplateKHR'
--
-- == Valid Usage (Implicit)
--
-- -   @commandBuffer@ /must/ be a valid
--     'Vulkan.Core10.Handles.CommandBuffer' handle
--
-- -   @descriptorUpdateTemplate@ /must/ be a valid
--     'Vulkan.Core11.Handles.DescriptorUpdateTemplate' handle
--
-- -   @layout@ /must/ be a valid 'Vulkan.Core10.Handles.PipelineLayout'
--     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 graphics, or compute operations
--
-- -   Each of @commandBuffer@, @descriptorUpdateTemplate@, and @layout@
--     /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                                                                                                                    | Both                                                                                                                   | Graphics                                                                                                              |                                                                                                                                     |
-- | Secondary                                                                                                                  |                                                                                                                        | Compute                                                                                                               |                                                                                                                                     |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- __API example.__
--
-- > struct AppDataStructure
-- > {
-- >     VkDescriptorImageInfo  imageInfo;          // a single image info
-- >     // ... some more application related data
-- > };
-- >
-- > const VkDescriptorUpdateTemplateEntry descriptorUpdateTemplateEntries[] =
-- > {
-- >     // binding to a single image descriptor
-- >     {
-- >         0,                                           // binding
-- >         0,                                           // dstArrayElement
-- >         1,                                           // descriptorCount
-- >         VK_DESCRIPTOR_TYPE_COMBINED_IMAGE_SAMPLER,   // descriptorType
-- >         offsetof(AppDataStructure, imageInfo),       // offset
-- >         0                                            // stride is not required if descriptorCount is 1
-- >     }
-- > };
-- >
-- > // create a descriptor update template for descriptor set updates
-- > const VkDescriptorUpdateTemplateCreateInfo createInfo =
-- > {
-- >     VK_STRUCTURE_TYPE_DESCRIPTOR_UPDATE_TEMPLATE_CREATE_INFO,  // sType
-- >     NULL,                                                      // pNext
-- >     0,                                                         // flags
-- >     1,                                                         // descriptorUpdateEntryCount
-- >     descriptorUpdateTemplateEntries,                           // pDescriptorUpdateEntries
-- >     VK_DESCRIPTOR_UPDATE_TEMPLATE_TYPE_PUSH_DESCRIPTORS_KHR,   // templateType
-- >     0,                                                         // descriptorSetLayout, ignored by given templateType
-- >     VK_PIPELINE_BIND_POINT_GRAPHICS,                           // pipelineBindPoint
-- >     myPipelineLayout,                                          // pipelineLayout
-- >     0,                                                         // set
-- > };
-- >
-- > VkDescriptorUpdateTemplate myDescriptorUpdateTemplate;
-- > myResult = vkCreateDescriptorUpdateTemplate(
-- >     myDevice,
-- >     &createInfo,
-- >     NULL,
-- >     &myDescriptorUpdateTemplate);
-- > }
-- >
-- > AppDataStructure appData;
-- > // fill appData here or cache it in your engine
-- > vkCmdPushDescriptorSetWithTemplateKHR(myCmdBuffer, myDescriptorUpdateTemplate, myPipelineLayout, 0,&appData);
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.CommandBuffer',
-- 'Vulkan.Core11.Handles.DescriptorUpdateTemplate',
-- 'Vulkan.Core10.Handles.PipelineLayout'
cmdPushDescriptorSetWithTemplateKHR :: forall io
                                     . (MonadIO io)
                                    => -- | @commandBuffer@ is the command buffer that the descriptors will be
                                       -- recorded in.
                                       CommandBuffer
                                    -> -- | @descriptorUpdateTemplate@ is a descriptor update template defining how
                                       -- to interpret the descriptor information in @pData@.
                                       DescriptorUpdateTemplate
                                    -> -- | @layout@ is a 'Vulkan.Core10.Handles.PipelineLayout' object used to
                                       -- program the bindings. It /must/ be compatible with the layout used to
                                       -- create the @descriptorUpdateTemplate@ handle.
                                       PipelineLayout
                                    -> -- | @set@ is the set number of the descriptor set in the pipeline layout
                                       -- that will be updated. This /must/ be the same number used to create the
                                       -- @descriptorUpdateTemplate@ handle.
                                       ("set" ::: Word32)
                                    -> -- | @pData@ is a pointer to memory containing descriptors for the templated
                                       -- update.
                                       ("data" ::: Ptr ())
                                    -> io ()
cmdPushDescriptorSetWithTemplateKHR :: CommandBuffer
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> io ()
cmdPushDescriptorSetWithTemplateKHR commandBuffer :: CommandBuffer
commandBuffer descriptorUpdateTemplate :: DescriptorUpdateTemplate
descriptorUpdateTemplate layout :: PipelineLayout
layout set :: "set" ::: Word32
set 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 vkCmdPushDescriptorSetWithTemplateKHRPtr :: FunPtr
  (Ptr CommandBuffer_T
   -> DescriptorUpdateTemplate
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
vkCmdPushDescriptorSetWithTemplateKHRPtr = DeviceCmds
-> FunPtr
     (Ptr CommandBuffer_T
      -> DescriptorUpdateTemplate
      -> PipelineLayout
      -> ("set" ::: Word32)
      -> ("data" ::: Ptr ())
      -> IO ())
pVkCmdPushDescriptorSetWithTemplateKHR (CommandBuffer -> DeviceCmds
deviceCmds (CommandBuffer
commandBuffer :: CommandBuffer))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr CommandBuffer_T
   -> DescriptorUpdateTemplate
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
vkCmdPushDescriptorSetWithTemplateKHRPtr FunPtr
  (Ptr CommandBuffer_T
   -> DescriptorUpdateTemplate
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
-> FunPtr
     (Ptr CommandBuffer_T
      -> DescriptorUpdateTemplate
      -> PipelineLayout
      -> ("set" ::: Word32)
      -> ("data" ::: Ptr ())
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr CommandBuffer_T
   -> DescriptorUpdateTemplate
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("data" ::: Ptr ())
   -> 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 vkCmdPushDescriptorSetWithTemplateKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCmdPushDescriptorSetWithTemplateKHR' :: Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ()
vkCmdPushDescriptorSetWithTemplateKHR' = FunPtr
  (Ptr CommandBuffer_T
   -> DescriptorUpdateTemplate
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
-> Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ()
mkVkCmdPushDescriptorSetWithTemplateKHR FunPtr
  (Ptr CommandBuffer_T
   -> DescriptorUpdateTemplate
   -> PipelineLayout
   -> ("set" ::: Word32)
   -> ("data" ::: Ptr ())
   -> IO ())
vkCmdPushDescriptorSetWithTemplateKHRPtr
  Ptr CommandBuffer_T
-> DescriptorUpdateTemplate
-> PipelineLayout
-> ("set" ::: Word32)
-> ("data" ::: Ptr ())
-> IO ()
vkCmdPushDescriptorSetWithTemplateKHR' (CommandBuffer -> Ptr CommandBuffer_T
commandBufferHandle (CommandBuffer
commandBuffer)) (DescriptorUpdateTemplate
descriptorUpdateTemplate) (PipelineLayout
layout) ("set" ::: Word32
set) ("data" ::: Ptr ()
data')
  () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()


-- | VkPhysicalDevicePushDescriptorPropertiesKHR - Structure describing push
-- descriptor limits that can be supported by an implementation
--
-- = Members
--
-- The members of the 'PhysicalDevicePushDescriptorPropertiesKHR' structure
-- describe the following implementation-dependent limits:
--
-- = Description
--
-- If the 'PhysicalDevicePushDescriptorPropertiesKHR' 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.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data PhysicalDevicePushDescriptorPropertiesKHR = PhysicalDevicePushDescriptorPropertiesKHR
  { -- | @maxPushDescriptors@ is the maximum number of descriptors that /can/ be
    -- used in a descriptor set created with
    -- 'Vulkan.Core10.Enums.DescriptorSetLayoutCreateFlagBits.DESCRIPTOR_SET_LAYOUT_CREATE_PUSH_DESCRIPTOR_BIT_KHR'
    -- set.
    PhysicalDevicePushDescriptorPropertiesKHR -> "set" ::: Word32
maxPushDescriptors :: Word32 }
  deriving (Typeable, PhysicalDevicePushDescriptorPropertiesKHR
-> PhysicalDevicePushDescriptorPropertiesKHR -> Bool
(PhysicalDevicePushDescriptorPropertiesKHR
 -> PhysicalDevicePushDescriptorPropertiesKHR -> Bool)
-> (PhysicalDevicePushDescriptorPropertiesKHR
    -> PhysicalDevicePushDescriptorPropertiesKHR -> Bool)
-> Eq PhysicalDevicePushDescriptorPropertiesKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhysicalDevicePushDescriptorPropertiesKHR
-> PhysicalDevicePushDescriptorPropertiesKHR -> Bool
$c/= :: PhysicalDevicePushDescriptorPropertiesKHR
-> PhysicalDevicePushDescriptorPropertiesKHR -> Bool
== :: PhysicalDevicePushDescriptorPropertiesKHR
-> PhysicalDevicePushDescriptorPropertiesKHR -> Bool
$c== :: PhysicalDevicePushDescriptorPropertiesKHR
-> PhysicalDevicePushDescriptorPropertiesKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PhysicalDevicePushDescriptorPropertiesKHR)
#endif
deriving instance Show PhysicalDevicePushDescriptorPropertiesKHR

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

instance FromCStruct PhysicalDevicePushDescriptorPropertiesKHR where
  peekCStruct :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> IO PhysicalDevicePushDescriptorPropertiesKHR
peekCStruct p :: Ptr PhysicalDevicePushDescriptorPropertiesKHR
p = do
    "set" ::: Word32
maxPushDescriptors <- Ptr ("set" ::: Word32) -> IO ("set" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PhysicalDevicePushDescriptorPropertiesKHR
p Ptr PhysicalDevicePushDescriptorPropertiesKHR
-> Int -> Ptr ("set" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    PhysicalDevicePushDescriptorPropertiesKHR
-> IO PhysicalDevicePushDescriptorPropertiesKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PhysicalDevicePushDescriptorPropertiesKHR
 -> IO PhysicalDevicePushDescriptorPropertiesKHR)
-> PhysicalDevicePushDescriptorPropertiesKHR
-> IO PhysicalDevicePushDescriptorPropertiesKHR
forall a b. (a -> b) -> a -> b
$ ("set" ::: Word32) -> PhysicalDevicePushDescriptorPropertiesKHR
PhysicalDevicePushDescriptorPropertiesKHR
             "set" ::: Word32
maxPushDescriptors

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

instance Zero PhysicalDevicePushDescriptorPropertiesKHR where
  zero :: PhysicalDevicePushDescriptorPropertiesKHR
zero = ("set" ::: Word32) -> PhysicalDevicePushDescriptorPropertiesKHR
PhysicalDevicePushDescriptorPropertiesKHR
           "set" ::: Word32
forall a. Zero a => a
zero


type KHR_PUSH_DESCRIPTOR_SPEC_VERSION = 2

-- No documentation found for TopLevel "VK_KHR_PUSH_DESCRIPTOR_SPEC_VERSION"
pattern KHR_PUSH_DESCRIPTOR_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_PUSH_DESCRIPTOR_SPEC_VERSION :: a
$mKHR_PUSH_DESCRIPTOR_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
KHR_PUSH_DESCRIPTOR_SPEC_VERSION = 2


type KHR_PUSH_DESCRIPTOR_EXTENSION_NAME = "VK_KHR_push_descriptor"

-- No documentation found for TopLevel "VK_KHR_PUSH_DESCRIPTOR_EXTENSION_NAME"
pattern KHR_PUSH_DESCRIPTOR_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_PUSH_DESCRIPTOR_EXTENSION_NAME :: a
$mKHR_PUSH_DESCRIPTOR_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
KHR_PUSH_DESCRIPTOR_EXTENSION_NAME = "VK_KHR_push_descriptor"