{-# language CPP #-}
module Vulkan.Core10.Queue  ( getDeviceQueue
                            , queueSubmit
                            , queueWaitIdle
                            , queueWaitIdleSafe
                            , deviceWaitIdle
                            , deviceWaitIdleSafe
                            , SubmitInfo(..)
                            , Queue(..)
                            , PipelineStageFlagBits(..)
                            , PipelineStageFlags
                            ) where

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
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.Utils (advancePtrBytes)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Extends (pokeSomeCStruct)
import Vulkan.NamedType ((:::))
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (CommandBuffer_T)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_external_semaphore_win32 (D3D12FenceSubmitInfoKHR)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkDeviceWaitIdle))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceQueue))
import Vulkan.Dynamic (DeviceCmds(pVkQueueSubmit))
import Vulkan.Dynamic (DeviceCmds(pVkQueueWaitIdle))
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_group (DeviceGroupSubmitInfo)
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.Core10.Handles (Fence)
import Vulkan.Core10.Handles (Fence(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_performance_query (PerformanceQuerySubmitInfoKHR)
import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlags)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import {-# SOURCE #-} Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory (ProtectedSubmitInfo)
import Vulkan.Core10.Handles (Queue)
import Vulkan.Core10.Handles (Queue(..))
import Vulkan.Core10.Handles (Queue(Queue))
import Vulkan.Core10.Handles (Queue_T)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Handles (Semaphore)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore (TimelineSemaphoreSubmitInfo)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_win32_keyed_mutex (Win32KeyedMutexAcquireReleaseInfoKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_win32_keyed_mutex (Win32KeyedMutexAcquireReleaseInfoNV)
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_SUBMIT_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlagBits(..))
import Vulkan.Core10.Enums.PipelineStageFlagBits (PipelineStageFlags)
import Vulkan.Core10.Handles (Queue(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkGetDeviceQueue
  :: FunPtr (Ptr Device_T -> Word32 -> Word32 -> Ptr (Ptr Queue_T) -> IO ()) -> Ptr Device_T -> Word32 -> Word32 -> Ptr (Ptr Queue_T) -> IO ()

-- | vkGetDeviceQueue - Get a queue handle from a device
--
-- = Description
--
-- 'getDeviceQueue' /must/ only be used to get queues that were created
-- with the @flags@ parameter of
-- 'Vulkan.Core10.Device.DeviceQueueCreateInfo' set to zero. To get queues
-- that were created with a non-zero @flags@ parameter use
-- 'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.getDeviceQueue2'.
--
-- == Valid Usage
--
-- -   @queueFamilyIndex@ /must/ be one of the queue family indices
--     specified when @device@ was created, via the
--     'Vulkan.Core10.Device.DeviceQueueCreateInfo' structure
--
-- -   @queueIndex@ /must/ be less than the number of queues created for
--     the specified queue family index when @device@ was created, via the
--     @queueCount@ member of the
--     'Vulkan.Core10.Device.DeviceQueueCreateInfo' structure
--
-- -   'Vulkan.Core10.Device.DeviceQueueCreateInfo'::@flags@ /must/ have
--     been set to zero when @device@ was created
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @pQueue@ /must/ be a valid pointer to a
--     'Vulkan.Core10.Handles.Queue' handle
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Queue'
getDeviceQueue :: forall io
                . (MonadIO io)
               => -- | @device@ is the logical device that owns the queue.
                  Device
               -> -- | @queueFamilyIndex@ is the index of the queue family to which the queue
                  -- belongs.
                  ("queueFamilyIndex" ::: Word32)
               -> -- | @queueIndex@ is the index within this queue family of the queue to
                  -- retrieve.
                  ("queueIndex" ::: Word32)
               -> io (Queue)
getDeviceQueue :: Device
-> ("queueFamilyIndex" ::: Word32)
-> ("queueFamilyIndex" ::: Word32)
-> io Queue
getDeviceQueue device :: Device
device queueFamilyIndex :: "queueFamilyIndex" ::: Word32
queueFamilyIndex queueIndex :: "queueFamilyIndex" ::: Word32
queueIndex = IO Queue -> io Queue
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Queue -> io Queue)
-> (ContT Queue IO Queue -> IO Queue)
-> ContT Queue IO Queue
-> io Queue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Queue IO Queue -> IO Queue
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Queue IO Queue -> io Queue)
-> ContT Queue IO Queue -> io Queue
forall a b. (a -> b) -> a -> b
$ do
  let cmds :: DeviceCmds
cmds = Device -> DeviceCmds
deviceCmds (Device
device :: Device)
  let vkGetDeviceQueuePtr :: FunPtr
  (Ptr Device_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pQueue" ::: Ptr (Ptr Queue_T))
   -> IO ())
vkGetDeviceQueuePtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("queueFamilyIndex" ::: Word32)
      -> ("queueFamilyIndex" ::: Word32)
      -> ("pQueue" ::: Ptr (Ptr Queue_T))
      -> IO ())
pVkGetDeviceQueue DeviceCmds
cmds
  IO () -> ContT Queue IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Queue IO ()) -> IO () -> ContT Queue IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pQueue" ::: Ptr (Ptr Queue_T))
   -> IO ())
vkGetDeviceQueuePtr FunPtr
  (Ptr Device_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pQueue" ::: Ptr (Ptr Queue_T))
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> ("queueFamilyIndex" ::: Word32)
      -> ("queueFamilyIndex" ::: Word32)
      -> ("pQueue" ::: Ptr (Ptr Queue_T))
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pQueue" ::: Ptr (Ptr Queue_T))
   -> 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 vkGetDeviceQueue is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeviceQueue' :: Ptr Device_T
-> ("queueFamilyIndex" ::: Word32)
-> ("queueFamilyIndex" ::: Word32)
-> ("pQueue" ::: Ptr (Ptr Queue_T))
-> IO ()
vkGetDeviceQueue' = FunPtr
  (Ptr Device_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pQueue" ::: Ptr (Ptr Queue_T))
   -> IO ())
-> Ptr Device_T
-> ("queueFamilyIndex" ::: Word32)
-> ("queueFamilyIndex" ::: Word32)
-> ("pQueue" ::: Ptr (Ptr Queue_T))
-> IO ()
mkVkGetDeviceQueue FunPtr
  (Ptr Device_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pQueue" ::: Ptr (Ptr Queue_T))
   -> IO ())
vkGetDeviceQueuePtr
  "pQueue" ::: Ptr (Ptr Queue_T)
pPQueue <- ((("pQueue" ::: Ptr (Ptr Queue_T)) -> IO Queue) -> IO Queue)
-> ContT Queue IO ("pQueue" ::: Ptr (Ptr Queue_T))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pQueue" ::: Ptr (Ptr Queue_T)) -> IO Queue) -> IO Queue)
 -> ContT Queue IO ("pQueue" ::: Ptr (Ptr Queue_T)))
-> ((("pQueue" ::: Ptr (Ptr Queue_T)) -> IO Queue) -> IO Queue)
-> ContT Queue IO ("pQueue" ::: Ptr (Ptr Queue_T))
forall a b. (a -> b) -> a -> b
$ IO ("pQueue" ::: Ptr (Ptr Queue_T))
-> (("pQueue" ::: Ptr (Ptr Queue_T)) -> IO ())
-> (("pQueue" ::: Ptr (Ptr Queue_T)) -> IO Queue)
-> IO Queue
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pQueue" ::: Ptr (Ptr Queue_T))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr Queue_T) 8) ("pQueue" ::: Ptr (Ptr Queue_T)) -> IO ()
forall a. Ptr a -> IO ()
free
  IO () -> ContT Queue IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Queue IO ()) -> IO () -> ContT Queue IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("queueFamilyIndex" ::: Word32)
-> ("queueFamilyIndex" ::: Word32)
-> ("pQueue" ::: Ptr (Ptr Queue_T))
-> IO ()
vkGetDeviceQueue' (Device -> Ptr Device_T
deviceHandle (Device
device)) ("queueFamilyIndex" ::: Word32
queueFamilyIndex) ("queueFamilyIndex" ::: Word32
queueIndex) ("pQueue" ::: Ptr (Ptr Queue_T)
pPQueue)
  Ptr Queue_T
pQueue <- IO (Ptr Queue_T) -> ContT Queue IO (Ptr Queue_T)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (Ptr Queue_T) -> ContT Queue IO (Ptr Queue_T))
-> IO (Ptr Queue_T) -> ContT Queue IO (Ptr Queue_T)
forall a b. (a -> b) -> a -> b
$ ("pQueue" ::: Ptr (Ptr Queue_T)) -> IO (Ptr Queue_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Queue_T) "pQueue" ::: Ptr (Ptr Queue_T)
pPQueue
  Queue -> ContT Queue IO Queue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Queue -> ContT Queue IO Queue) -> Queue -> ContT Queue IO Queue
forall a b. (a -> b) -> a -> b
$ (((\h :: Ptr Queue_T
h -> Ptr Queue_T -> DeviceCmds -> Queue
Queue Ptr Queue_T
h DeviceCmds
cmds ) Ptr Queue_T
pQueue))


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkQueueSubmit
  :: FunPtr (Ptr Queue_T -> Word32 -> Ptr (SomeStruct SubmitInfo) -> Fence -> IO Result) -> Ptr Queue_T -> Word32 -> Ptr (SomeStruct SubmitInfo) -> Fence -> IO Result

-- | vkQueueSubmit - Submits a sequence of semaphores or command buffers to a
-- queue
--
-- = Description
--
-- 'queueSubmit' is a
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#devsandqueues-submission queue submission command>,
-- with each batch defined by an element of @pSubmits@. Batches begin
-- execution in the order they appear in @pSubmits@, but /may/ complete out
-- of order.
--
-- Fence and semaphore operations submitted with 'queueSubmit' have
-- additional ordering constraints compared to other submission commands,
-- with dependencies involving previous and subsequent queue operations.
-- Information about these additional constraints can be found in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-semaphores semaphore>
-- and
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-fences fence>
-- sections of
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization the synchronization chapter>.
--
-- Details on the interaction of @pWaitDstStageMask@ with synchronization
-- are described in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-semaphores-waiting semaphore wait operation>
-- section of
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization the synchronization chapter>.
--
-- The order that batches appear in @pSubmits@ is used to determine
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>,
-- and thus all the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-implicit implicit ordering guarantees>
-- that respect it. Other than these implicit ordering guarantees and any
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization explicit synchronization primitives>,
-- these batches /may/ overlap or otherwise execute out of order.
--
-- If any command buffer submitted to this queue is in the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle executable state>,
-- it is moved to the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle pending state>.
-- Once execution of all submissions of a command buffer complete, it moves
-- from the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle pending state>,
-- back to the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle executable state>.
-- If a command buffer was recorded with the
-- 'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_ONE_TIME_SUBMIT_BIT'
-- flag, it instead moves to the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle invalid state>.
--
-- If 'queueSubmit' fails, it /may/ return
-- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY' or
-- 'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'. If it does, the
-- implementation /must/ ensure that the state and contents of any
-- resources or synchronization primitives referenced by the submitted
-- command buffers and any semaphores referenced by @pSubmits@ is
-- unaffected by the call or its failure. If 'queueSubmit' fails in such a
-- way that the implementation is unable to make that guarantee, the
-- implementation /must/ return
-- 'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'. See
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#devsandqueues-lost-device Lost Device>.
--
-- == Valid Usage
--
-- -   If @fence@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @fence@
--     /must/ be unsignaled
--
-- -   If @fence@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @fence@
--     /must/ not be associated with any other queue command that has not
--     yet completed execution on that queue
--
-- -   Any calls to 'Vulkan.Core10.CommandBufferBuilding.cmdSetEvent',
--     'Vulkan.Core10.CommandBufferBuilding.cmdResetEvent' or
--     'Vulkan.Core10.CommandBufferBuilding.cmdWaitEvents' that have been
--     recorded into any of the command buffer elements of the
--     @pCommandBuffers@ member of any element of @pSubmits@, /must/ not
--     reference any 'Vulkan.Core10.Handles.Event' that is referenced by
--     any of those commands in a command buffer that has been submitted to
--     another queue and is still in the /pending state/
--
-- -   Any stage flag included in any element of the @pWaitDstStageMask@
--     member of any element of @pSubmits@ /must/ be a pipeline stage
--     supported by one of the capabilities of @queue@, as specified in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-pipeline-stages-supported table of supported pipeline stages>
--
-- -   Each element of the @pSignalSemaphores@ member of any element of
--     @pSubmits@ /must/ be unsignaled when the semaphore signal operation
--     it defines is executed on the device
--
-- -   When a semaphore wait operation referring to a binary semaphore
--     defined by any element of the @pWaitSemaphores@ member of any
--     element of @pSubmits@ executes on @queue@, there /must/ be no other
--     queues waiting on the same semaphore
--
-- -   All elements of the @pWaitSemaphores@ member of all elements of
--     @pSubmits@ created with a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_BINARY' /must/
--     reference a semaphore signal operation that has been submitted for
--     execution and any semaphore signal operations on which it depends
--     (if any) /must/ have also been submitted for execution
--
-- -   Each element of the @pCommandBuffers@ member of each element of
--     @pSubmits@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle pending or executable state>
--
-- -   If any element of the @pCommandBuffers@ member of any element of
--     @pSubmits@ was not recorded with the
--     'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT',
--     it /must/ not be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle pending state>
--
-- -   Any
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-secondary secondary command buffers recorded>
--     into any element of the @pCommandBuffers@ member of any element of
--     @pSubmits@ /must/ be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle pending or executable state>
--
-- -   If any
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-secondary secondary command buffers recorded>
--     into any element of the @pCommandBuffers@ member of any element of
--     @pSubmits@ was not recorded with the
--     'Vulkan.Core10.Enums.CommandBufferUsageFlagBits.COMMAND_BUFFER_USAGE_SIMULTANEOUS_USE_BIT',
--     it /must/ not be in the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#commandbuffers-lifecycle pending state>
--
-- -   Each element of the @pCommandBuffers@ member of each element of
--     @pSubmits@ /must/ have been allocated from a
--     'Vulkan.Core10.Handles.CommandPool' that was created for the same
--     queue family @queue@ belongs to
--
-- -   If any element of @pSubmits->pCommandBuffers@ includes a
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers-acquire Queue Family Transfer Acquire Operation>,
--     there /must/ exist a previously submitted
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers-release Queue Family Transfer Release Operation>
--     on a queue in the queue family identified by the acquire operation,
--     with parameters matching the acquire operation as defined in the
--     definition of such
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-queue-transfers-acquire acquire operations>,
--     and which happens-before the acquire operation
--
-- -   If a command recorded into any element of @pCommandBuffers@ was a
--     'Vulkan.Core10.CommandBufferBuilding.cmdBeginQuery' whose
--     @queryPool@ was created with a @queryType@ of
--     'Vulkan.Core10.Enums.QueryType.QUERY_TYPE_PERFORMANCE_QUERY_KHR',
--     the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#profiling-lock profiling lock>
--     /must/ have been held continuously on the
--     'Vulkan.Core10.Handles.Device' that @queue@ was retrieved from,
--     throughout recording of those command buffers
--
-- -   Any resource created with
--     'Vulkan.Core10.Enums.SharingMode.SHARING_MODE_EXCLUSIVE' that is
--     read by an operation specified by @pSubmits@ /must/ not be owned by
--     any queue family other than the one which @queue@ belongs to, at the
--     time it is executed
--
-- == Valid Usage (Implicit)
--
-- -   @queue@ /must/ be a valid 'Vulkan.Core10.Handles.Queue' handle
--
-- -   If @submitCount@ is not @0@, @pSubmits@ /must/ be a valid pointer to
--     an array of @submitCount@ valid 'SubmitInfo' structures
--
-- -   If @fence@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE', @fence@
--     /must/ be a valid 'Vulkan.Core10.Handles.Fence' handle
--
-- -   Both of @fence@, and @queue@ that are valid handles of non-ignored
--     parameters /must/ have been created, allocated, or retrieved from
--     the same 'Vulkan.Core10.Handles.Device'
--
-- == Host Synchronization
--
-- -   Host access to @queue@ /must/ be externally synchronized
--
-- -   Host access to @fence@ /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> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | -                                                                                                                          | -                                                                                                                      | Any                                                                                                                   | -                                                                                                                                   |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Fence', 'Vulkan.Core10.Handles.Queue',
-- 'SubmitInfo'
queueSubmit :: forall io
             . (MonadIO io)
            => -- | @queue@ is the queue that the command buffers will be submitted to.
               Queue
            -> -- | @pSubmits@ is a pointer to an array of 'SubmitInfo' structures, each
               -- specifying a command buffer submission batch.
               ("submits" ::: Vector (SomeStruct SubmitInfo))
            -> -- | @fence@ is an /optional/ handle to a fence to be signaled once all
               -- submitted command buffers have completed execution. If @fence@ is not
               -- 'Vulkan.Core10.APIConstants.NULL_HANDLE', it defines a
               -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-fences-signaling fence signal operation>.
               Fence
            -> io ()
queueSubmit :: Queue
-> ("submits" ::: Vector (SomeStruct SubmitInfo)) -> Fence -> io ()
queueSubmit queue :: Queue
queue submits :: "submits" ::: Vector (SomeStruct SubmitInfo)
submits fence :: Fence
fence = 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 vkQueueSubmitPtr :: FunPtr
  (Ptr Queue_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
   -> Fence
   -> IO Result)
vkQueueSubmitPtr = DeviceCmds
-> FunPtr
     (Ptr Queue_T
      -> ("queueFamilyIndex" ::: Word32)
      -> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
      -> Fence
      -> IO Result)
pVkQueueSubmit (Queue -> DeviceCmds
deviceCmds (Queue
queue :: Queue))
  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 Queue_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
   -> Fence
   -> IO Result)
vkQueueSubmitPtr FunPtr
  (Ptr Queue_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
   -> Fence
   -> IO Result)
-> FunPtr
     (Ptr Queue_T
      -> ("queueFamilyIndex" ::: Word32)
      -> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
      -> Fence
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Queue_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
   -> Fence
   -> 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 vkQueueSubmit is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkQueueSubmit' :: Ptr Queue_T
-> ("queueFamilyIndex" ::: Word32)
-> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
-> Fence
-> IO Result
vkQueueSubmit' = FunPtr
  (Ptr Queue_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
   -> Fence
   -> IO Result)
-> Ptr Queue_T
-> ("queueFamilyIndex" ::: Word32)
-> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
-> Fence
-> IO Result
mkVkQueueSubmit FunPtr
  (Ptr Queue_T
   -> ("queueFamilyIndex" ::: Word32)
   -> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
   -> Fence
   -> IO Result)
vkQueueSubmitPtr
  Ptr (SubmitInfo Any)
pPSubmits <- ((Ptr (SubmitInfo Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (SubmitInfo Any))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (SubmitInfo Any) -> IO ()) -> IO ())
 -> ContT () IO (Ptr (SubmitInfo Any)))
-> ((Ptr (SubmitInfo Any) -> IO ()) -> IO ())
-> ContT () IO (Ptr (SubmitInfo Any))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (SubmitInfo Any) -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(SubmitInfo _) ((("submits" ::: Vector (SomeStruct SubmitInfo)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("submits" ::: Vector (SomeStruct SubmitInfo)
submits)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 72) 8
  (Int -> SomeStruct SubmitInfo -> ContT () IO ())
-> ("submits" ::: Vector (SomeStruct SubmitInfo)) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: SomeStruct SubmitInfo
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
$ ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
-> SomeStruct SubmitInfo -> 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 (SubmitInfo Any) -> "pSubmits" ::: Ptr (SomeStruct SubmitInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (SubmitInfo Any)
pPSubmits Ptr (SubmitInfo Any) -> Int -> Ptr (SubmitInfo _)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (72 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (SubmitInfo _))) (SomeStruct SubmitInfo
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
$ ())) ("submits" ::: Vector (SomeStruct SubmitInfo)
submits)
  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 Queue_T
-> ("queueFamilyIndex" ::: Word32)
-> ("pSubmits" ::: Ptr (SomeStruct SubmitInfo))
-> Fence
-> IO Result
vkQueueSubmit' (Queue -> Ptr Queue_T
queueHandle (Queue
queue)) ((Int -> "queueFamilyIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("submits" ::: Vector (SomeStruct SubmitInfo)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("submits" ::: Vector (SomeStruct SubmitInfo)) -> Int)
-> ("submits" ::: Vector (SomeStruct SubmitInfo)) -> Int
forall a b. (a -> b) -> a -> b
$ ("submits" ::: Vector (SomeStruct SubmitInfo)
submits)) :: Word32)) (Ptr (SubmitInfo Any) -> "pSubmits" ::: Ptr (SomeStruct SubmitInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions (Ptr (SubmitInfo Any)
pPSubmits)) (Fence
fence)
  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" mkVkQueueWaitIdleUnsafe
  :: FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result

foreign import ccall
  "dynamic" mkVkQueueWaitIdleSafe
  :: FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result

-- | queueWaitIdle with selectable safeness
queueWaitIdleSafeOrUnsafe :: forall io
                           . (MonadIO io)
                          => -- No documentation found for TopLevel ""
                             (FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result)
                          -> -- | @queue@ is the queue on which to wait.
                             Queue
                          -> io ()
queueWaitIdleSafeOrUnsafe :: (FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result)
-> Queue -> io ()
queueWaitIdleSafeOrUnsafe mkVkQueueWaitIdle :: FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result
mkVkQueueWaitIdle queue :: Queue
queue = 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 vkQueueWaitIdlePtr :: FunPtr (Ptr Queue_T -> IO Result)
vkQueueWaitIdlePtr = DeviceCmds -> FunPtr (Ptr Queue_T -> IO Result)
pVkQueueWaitIdle (Queue -> DeviceCmds
deviceCmds (Queue
queue :: Queue))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Queue_T -> IO Result)
vkQueueWaitIdlePtr FunPtr (Ptr Queue_T -> IO Result)
-> FunPtr (Ptr Queue_T -> IO Result) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Queue_T -> 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 vkQueueWaitIdle is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkQueueWaitIdle' :: Ptr Queue_T -> IO Result
vkQueueWaitIdle' = FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result
mkVkQueueWaitIdle FunPtr (Ptr Queue_T -> IO Result)
vkQueueWaitIdlePtr
  Result
r <- Ptr Queue_T -> IO Result
vkQueueWaitIdle' (Queue -> Ptr Queue_T
queueHandle (Queue
queue))
  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))

-- | vkQueueWaitIdle - Wait for a queue to become idle
--
-- = Description
--
-- 'queueWaitIdle' is equivalent to submitting a fence to a queue and
-- waiting with an infinite timeout for that fence to signal.
--
-- == Valid Usage (Implicit)
--
-- -   @queue@ /must/ be a valid 'Vulkan.Core10.Handles.Queue' handle
--
-- == Host Synchronization
--
-- -   Host access to @queue@ /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> |
-- +============================================================================================================================+========================================================================================================================+=======================================================================================================================+=====================================================================================================================================+
-- | -                                                                                                                          | -                                                                                                                      | Any                                                                                                                   | -                                                                                                                                   |
-- +----------------------------------------------------------------------------------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+-----------------------------------------------------------------------------------------------------------------------+-------------------------------------------------------------------------------------------------------------------------------------+
--
-- == 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'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Queue'
queueWaitIdle :: forall io
               . (MonadIO io)
              => -- | @queue@ is the queue on which to wait.
                 Queue
              -> io ()
queueWaitIdle :: Queue -> io ()
queueWaitIdle = (FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result)
-> Queue -> io ()
forall (io :: * -> *).
MonadIO io =>
(FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result)
-> Queue -> io ()
queueWaitIdleSafeOrUnsafe FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result
mkVkQueueWaitIdleUnsafe

-- | A variant of 'queueWaitIdle' which makes a *safe* FFI call
queueWaitIdleSafe :: forall io
                   . (MonadIO io)
                  => -- | @queue@ is the queue on which to wait.
                     Queue
                  -> io ()
queueWaitIdleSafe :: Queue -> io ()
queueWaitIdleSafe = (FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result)
-> Queue -> io ()
forall (io :: * -> *).
MonadIO io =>
(FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result)
-> Queue -> io ()
queueWaitIdleSafeOrUnsafe FunPtr (Ptr Queue_T -> IO Result) -> Ptr Queue_T -> IO Result
mkVkQueueWaitIdleSafe


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

foreign import ccall
  "dynamic" mkVkDeviceWaitIdleSafe
  :: FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result

-- | deviceWaitIdle with selectable safeness
deviceWaitIdleSafeOrUnsafe :: forall io
                            . (MonadIO io)
                           => -- No documentation found for TopLevel ""
                              (FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result)
                           -> -- | @device@ is the logical device to idle.
                              Device
                           -> io ()
deviceWaitIdleSafeOrUnsafe :: (FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result)
-> Device -> io ()
deviceWaitIdleSafeOrUnsafe mkVkDeviceWaitIdle :: FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result
mkVkDeviceWaitIdle device :: Device
device = 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 vkDeviceWaitIdlePtr :: FunPtr (Ptr Device_T -> IO Result)
vkDeviceWaitIdlePtr = DeviceCmds -> FunPtr (Ptr Device_T -> IO Result)
pVkDeviceWaitIdle (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> IO Result)
vkDeviceWaitIdlePtr FunPtr (Ptr Device_T -> IO Result)
-> FunPtr (Ptr Device_T -> IO Result) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> 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 vkDeviceWaitIdle is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDeviceWaitIdle' :: Ptr Device_T -> IO Result
vkDeviceWaitIdle' = FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result
mkVkDeviceWaitIdle FunPtr (Ptr Device_T -> IO Result)
vkDeviceWaitIdlePtr
  Result
r <- Ptr Device_T -> IO Result
vkDeviceWaitIdle' (Device -> Ptr Device_T
deviceHandle (Device
device))
  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))

-- | vkDeviceWaitIdle - Wait for a device to become idle
--
-- = Description
--
-- 'deviceWaitIdle' is equivalent to calling 'queueWaitIdle' for all queues
-- owned by @device@.
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- == Host Synchronization
--
-- -   Host access to all 'Vulkan.Core10.Handles.Queue' objects created
--     from @device@ /must/ be externally synchronized
--
-- == 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'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'
--
-- = See Also
--
-- 'Vulkan.Core10.Handles.Device'
deviceWaitIdle :: forall io
                . (MonadIO io)
               => -- | @device@ is the logical device to idle.
                  Device
               -> io ()
deviceWaitIdle :: Device -> io ()
deviceWaitIdle = (FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result)
-> Device -> io ()
forall (io :: * -> *).
MonadIO io =>
(FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result)
-> Device -> io ()
deviceWaitIdleSafeOrUnsafe FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result
mkVkDeviceWaitIdleUnsafe

-- | A variant of 'deviceWaitIdle' which makes a *safe* FFI call
deviceWaitIdleSafe :: forall io
                    . (MonadIO io)
                   => -- | @device@ is the logical device to idle.
                      Device
                   -> io ()
deviceWaitIdleSafe :: Device -> io ()
deviceWaitIdleSafe = (FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result)
-> Device -> io ()
forall (io :: * -> *).
MonadIO io =>
(FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result)
-> Device -> io ()
deviceWaitIdleSafeOrUnsafe FunPtr (Ptr Device_T -> IO Result) -> Ptr Device_T -> IO Result
mkVkDeviceWaitIdleSafe


-- | VkSubmitInfo - Structure specifying a queue submit operation
--
-- = Description
--
-- The order that command buffers appear in @pCommandBuffers@ is used to
-- determine
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-submission-order submission order>,
-- and thus all the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-implicit implicit ordering guarantees>
-- that respect it. Other than these implicit ordering guarantees and any
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization explicit synchronization primitives>,
-- these command buffers /may/ overlap or otherwise execute out of order.
--
-- == Valid Usage
--
-- -   Each element of @pCommandBuffers@ /must/ not have been allocated
--     with
--     'Vulkan.Core10.Enums.CommandBufferLevel.COMMAND_BUFFER_LEVEL_SECONDARY'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-geometryShader geometry shaders>
--     feature is not enabled, each element of @pWaitDstStageMask@ /must/
--     not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_GEOMETRY_SHADER_BIT'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-tessellationShader tessellation shaders>
--     feature is not enabled, each element of @pWaitDstStageMask@ /must/
--     not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_CONTROL_SHADER_BIT'
--     or
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TESSELLATION_EVALUATION_SHADER_BIT'
--
-- -   Each element of @pWaitDstStageMask@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_HOST_BIT'
--
-- -   If any element of @pWaitSemaphores@ or @pSignalSemaphores@ was
--     created with a 'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_TIMELINE', then
--     the @pNext@ chain /must/ include a
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.TimelineSemaphoreSubmitInfo'
--     structure
--
-- -   If the @pNext@ chain of this structure includes a
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.TimelineSemaphoreSubmitInfo'
--     structure and any element of @pWaitSemaphores@ was created with a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_TIMELINE', then
--     its @waitSemaphoreValueCount@ member /must/ equal
--     @waitSemaphoreCount@
--
-- -   If the @pNext@ chain of this structure includes a
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.TimelineSemaphoreSubmitInfo'
--     structure and any element of @pSignalSemaphores@ was created with a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_TIMELINE', then
--     its @signalSemaphoreValueCount@ member /must/ equal
--     @signalSemaphoreCount@
--
-- -   For each element of @pSignalSemaphores@ created with a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_TIMELINE' the
--     corresponding element of
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.TimelineSemaphoreSubmitInfo'::pSignalSemaphoreValues
--     /must/ have a value greater than the current value of the semaphore
--     when the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-semaphores-signaling semaphore signal operation>
--     is executed
--
-- -   For each element of @pWaitSemaphores@ created with a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_TIMELINE' the
--     corresponding element of
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.TimelineSemaphoreSubmitInfo'::pWaitSemaphoreValues
--     /must/ have a value which does not differ from the current value of
--     the semaphore or the value of any outstanding semaphore wait or
--     signal operation on that semaphore by more than
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxTimelineSemaphoreValueDifference maxTimelineSemaphoreValueDifference>
--
-- -   For each element of @pSignalSemaphores@ created with a
--     'Vulkan.Core12.Enums.SemaphoreType.SemaphoreType' of
--     'Vulkan.Core12.Enums.SemaphoreType.SEMAPHORE_TYPE_TIMELINE' the
--     corresponding element of
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.TimelineSemaphoreSubmitInfo'::pSignalSemaphoreValues
--     /must/ have a value which does not differ from the current value of
--     the semaphore or the value of any outstanding semaphore wait or
--     signal operation on that semaphore by more than
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#limits-maxTimelineSemaphoreValueDifference maxTimelineSemaphoreValueDifference>
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-meshShader mesh shaders>
--     feature is not enabled, each element of @pWaitDstStageMask@ /must/
--     not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_MESH_SHADER_BIT_NV'
--
-- -   If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-taskShader task shaders>
--     feature is not enabled, each element of @pWaitDstStageMask@ /must/
--     not contain
--     'Vulkan.Core10.Enums.PipelineStageFlagBits.PIPELINE_STAGE_TASK_SHADER_BIT_NV'
--
-- -   If the @pNext@ chain of this structure does not include a
--     'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.ProtectedSubmitInfo'
--     structure with @protectedSubmit@ set to
--     'Vulkan.Core10.FundamentalTypes.TRUE', then each element of the
--     @pCommandBuffers@ array /must/ be an unprotected command buffer
--
-- -   If the @pNext@ chain of this structure includes a
--     'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.ProtectedSubmitInfo'
--     structure with @protectedSubmit@ set to
--     'Vulkan.Core10.FundamentalTypes.TRUE', then each element of the
--     @pCommandBuffers@ array /must/ be an protected command buffer
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_SUBMIT_INFO'
--
-- -   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_external_semaphore_win32.D3D12FenceSubmitInfoKHR',
--     'Vulkan.Core11.Promoted_From_VK_KHR_device_group.DeviceGroupSubmitInfo',
--     'Vulkan.Extensions.VK_KHR_performance_query.PerformanceQuerySubmitInfoKHR',
--     'Vulkan.Core11.Originally_Based_On_VK_KHR_protected_memory.ProtectedSubmitInfo',
--     'Vulkan.Core12.Promoted_From_VK_KHR_timeline_semaphore.TimelineSemaphoreSubmitInfo',
--     'Vulkan.Extensions.VK_KHR_win32_keyed_mutex.Win32KeyedMutexAcquireReleaseInfoKHR',
--     or
--     'Vulkan.Extensions.VK_NV_win32_keyed_mutex.Win32KeyedMutexAcquireReleaseInfoNV'
--
-- -   The @sType@ value of each struct in the @pNext@ chain /must/ be
--     unique
--
-- -   If @waitSemaphoreCount@ is not @0@, @pWaitSemaphores@ /must/ be a
--     valid pointer to an array of @waitSemaphoreCount@ valid
--     'Vulkan.Core10.Handles.Semaphore' handles
--
-- -   If @waitSemaphoreCount@ is not @0@, @pWaitDstStageMask@ /must/ be a
--     valid pointer to an array of @waitSemaphoreCount@ valid combinations
--     of 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlagBits'
--     values
--
-- -   Each element of @pWaitDstStageMask@ /must/ not be @0@
--
-- -   If @commandBufferCount@ is not @0@, @pCommandBuffers@ /must/ be a
--     valid pointer to an array of @commandBufferCount@ valid
--     'Vulkan.Core10.Handles.CommandBuffer' handles
--
-- -   If @signalSemaphoreCount@ is not @0@, @pSignalSemaphores@ /must/ be
--     a valid pointer to an array of @signalSemaphoreCount@ valid
--     'Vulkan.Core10.Handles.Semaphore' handles
--
-- -   Each of the elements of @pCommandBuffers@, the elements of
--     @pSignalSemaphores@, and the elements of @pWaitSemaphores@ 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.CommandBuffer',
-- 'Vulkan.Core10.Enums.PipelineStageFlagBits.PipelineStageFlags',
-- 'Vulkan.Core10.Handles.Semaphore',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'queueSubmit'
data SubmitInfo (es :: [Type]) = SubmitInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    SubmitInfo es -> Chain es
next :: Chain es
  , -- | @pWaitSemaphores@ is a pointer to an array of
    -- 'Vulkan.Core10.Handles.Semaphore' handles upon which to wait before the
    -- command buffers for this batch begin execution. If semaphores to wait on
    -- are provided, they define a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-semaphores-waiting semaphore wait operation>.
    SubmitInfo es -> Vector Semaphore
waitSemaphores :: Vector Semaphore
  , -- | @pWaitDstStageMask@ is a pointer to an array of pipeline stages at which
    -- each corresponding semaphore wait will occur.
    SubmitInfo es -> Vector PipelineStageFlags
waitDstStageMask :: Vector PipelineStageFlags
  , -- | @pCommandBuffers@ is a pointer to an array of
    -- 'Vulkan.Core10.Handles.CommandBuffer' handles to execute in the batch.
    SubmitInfo es -> Vector (Ptr CommandBuffer_T)
commandBuffers :: Vector (Ptr CommandBuffer_T)
  , -- | @pSignalSemaphores@ is a pointer to an array of
    -- 'Vulkan.Core10.Handles.Semaphore' handles which will be signaled when
    -- the command buffers for this batch have completed execution. If
    -- semaphores to be signaled are provided, they define a
    -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#synchronization-semaphores-signaling semaphore signal operation>.
    SubmitInfo es -> Vector Semaphore
signalSemaphores :: Vector Semaphore
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (SubmitInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (SubmitInfo es)

instance Extensible SubmitInfo where
  extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_SUBMIT_INFO
  setNext :: SubmitInfo ds -> Chain es -> SubmitInfo es
setNext x :: SubmitInfo ds
x next :: Chain es
next = SubmitInfo ds
x{$sel:next:SubmitInfo :: Chain es
next = Chain es
next}
  getNext :: SubmitInfo es -> Chain es
getNext SubmitInfo{..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends SubmitInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends SubmitInfo e => b) -> Maybe b
extends _ f :: Extends SubmitInfo e => b
f
    | Just Refl <- (Typeable e, Typeable PerformanceQuerySubmitInfoKHR) =>
Maybe (e :~: PerformanceQuerySubmitInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @PerformanceQuerySubmitInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SubmitInfo e => b
f
    | Just Refl <- (Typeable e, Typeable TimelineSemaphoreSubmitInfo) =>
Maybe (e :~: TimelineSemaphoreSubmitInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @TimelineSemaphoreSubmitInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SubmitInfo e => b
f
    | Just Refl <- (Typeable e, Typeable ProtectedSubmitInfo) =>
Maybe (e :~: ProtectedSubmitInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ProtectedSubmitInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SubmitInfo e => b
f
    | Just Refl <- (Typeable e, Typeable DeviceGroupSubmitInfo) =>
Maybe (e :~: DeviceGroupSubmitInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DeviceGroupSubmitInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SubmitInfo e => b
f
    | Just Refl <- (Typeable e, Typeable D3D12FenceSubmitInfoKHR) =>
Maybe (e :~: D3D12FenceSubmitInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @D3D12FenceSubmitInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SubmitInfo e => b
f
    | Just Refl <- (Typeable e, Typeable Win32KeyedMutexAcquireReleaseInfoKHR) =>
Maybe (e :~: Win32KeyedMutexAcquireReleaseInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @Win32KeyedMutexAcquireReleaseInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SubmitInfo e => b
f
    | Just Refl <- (Typeable e, Typeable Win32KeyedMutexAcquireReleaseInfoNV) =>
Maybe (e :~: Win32KeyedMutexAcquireReleaseInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @Win32KeyedMutexAcquireReleaseInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends SubmitInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss SubmitInfo es, PokeChain es) => ToCStruct (SubmitInfo es) where
  withCStruct :: SubmitInfo es -> (Ptr (SubmitInfo es) -> IO b) -> IO b
withCStruct x :: SubmitInfo es
x f :: Ptr (SubmitInfo es) -> IO b
f = Int -> Int -> (Ptr (SubmitInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 72 8 ((Ptr (SubmitInfo es) -> IO b) -> IO b)
-> (Ptr (SubmitInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (SubmitInfo es)
p -> Ptr (SubmitInfo es) -> SubmitInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (SubmitInfo es)
p SubmitInfo es
x (Ptr (SubmitInfo es) -> IO b
f Ptr (SubmitInfo es)
p)
  pokeCStruct :: Ptr (SubmitInfo es) -> SubmitInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (SubmitInfo es)
p SubmitInfo{..} 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 (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBMIT_INFO)
    Ptr ()
pNext'' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (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 (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (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 (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    let pWaitSemaphoresLength :: Int
pWaitSemaphoresLength = Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore -> Int) -> Vector Semaphore -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Semaphore
waitSemaphores)
    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 ((Vector PipelineStageFlags -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector PipelineStageFlags -> Int)
-> Vector PipelineStageFlags -> Int
forall a b. (a -> b) -> a -> b
$ (Vector PipelineStageFlags
waitDstStageMask)) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pWaitSemaphoresLength) (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 "" "pWaitDstStageMask and pWaitSemaphores must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
    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 ("queueFamilyIndex" ::: Word32)
-> ("queueFamilyIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr ("queueFamilyIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ((Int -> "queueFamilyIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pWaitSemaphoresLength :: Word32))
    Ptr Semaphore
pPWaitSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore
waitSemaphores)) 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 -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPWaitSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
waitSemaphores)
    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 Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPWaitSemaphores')
    Ptr PipelineStageFlags
pPWaitDstStageMask' <- ((Ptr PipelineStageFlags -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineStageFlags)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PipelineStageFlags -> IO b) -> IO b)
 -> ContT b IO (Ptr PipelineStageFlags))
-> ((Ptr PipelineStageFlags -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineStageFlags)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr PipelineStageFlags -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @PipelineStageFlags ((Vector PipelineStageFlags -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector PipelineStageFlags
waitDstStageMask)) 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 -> PipelineStageFlags -> IO ())
-> Vector PipelineStageFlags -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: PipelineStageFlags
e -> Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PipelineStageFlags
pPWaitDstStageMask' Ptr PipelineStageFlags -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineStageFlags) (PipelineStageFlags
e)) (Vector PipelineStageFlags
waitDstStageMask)
    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 PipelineStageFlags) -> Ptr PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr PipelineStageFlags)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr PipelineStageFlags))) (Ptr PipelineStageFlags
pPWaitDstStageMask')
    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 ("queueFamilyIndex" ::: Word32)
-> ("queueFamilyIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr ("queueFamilyIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32)) ((Int -> "queueFamilyIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector (Ptr CommandBuffer_T) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (Ptr CommandBuffer_T) -> Int)
-> Vector (Ptr CommandBuffer_T) -> Int
forall a b. (a -> b) -> a -> b
$ (Vector (Ptr CommandBuffer_T)
commandBuffers)) :: Word32))
    Ptr (Ptr CommandBuffer_T)
pPCommandBuffers' <- ((Ptr (Ptr CommandBuffer_T) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr CommandBuffer_T))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Ptr CommandBuffer_T) -> IO b) -> IO b)
 -> ContT b IO (Ptr (Ptr CommandBuffer_T)))
-> ((Ptr (Ptr CommandBuffer_T) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr CommandBuffer_T))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (Ptr CommandBuffer_T) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CommandBuffer_T) ((Vector (Ptr CommandBuffer_T) -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector (Ptr CommandBuffer_T)
commandBuffers)) 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 -> Ptr CommandBuffer_T -> IO ())
-> Vector (Ptr CommandBuffer_T) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Ptr CommandBuffer_T
e -> Ptr (Ptr CommandBuffer_T) -> Ptr CommandBuffer_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr (Ptr CommandBuffer_T)
pPCommandBuffers' Ptr (Ptr CommandBuffer_T) -> Int -> Ptr (Ptr CommandBuffer_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CommandBuffer_T)) (Ptr CommandBuffer_T
e)) (Vector (Ptr CommandBuffer_T)
commandBuffers)
    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 CommandBuffer_T))
-> Ptr (Ptr CommandBuffer_T) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr (Ptr CommandBuffer_T))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (Ptr CommandBuffer_T)))) (Ptr (Ptr CommandBuffer_T)
pPCommandBuffers')
    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 ("queueFamilyIndex" ::: Word32)
-> ("queueFamilyIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr ("queueFamilyIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32)) ((Int -> "queueFamilyIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore -> Int) -> Vector Semaphore -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Semaphore
signalSemaphores)) :: Word32))
    Ptr Semaphore
pPSignalSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((Vector Semaphore -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Semaphore
signalSemaphores)) 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 -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPSignalSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
signalSemaphores)
    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 Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPSignalSemaphores')
    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 (SubmitInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (SubmitInfo 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 (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_SUBMIT_INFO)
    Ptr ()
pNext' <- (Ptr (Chain es) -> Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO (Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
    -> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (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 (Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (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 (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    Ptr Semaphore
pPWaitSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((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 -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPWaitSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
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 Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPWaitSemaphores')
    Ptr PipelineStageFlags
pPWaitDstStageMask' <- ((Ptr PipelineStageFlags -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineStageFlags)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PipelineStageFlags -> IO b) -> IO b)
 -> ContT b IO (Ptr PipelineStageFlags))
-> ((Ptr PipelineStageFlags -> IO b) -> IO b)
-> ContT b IO (Ptr PipelineStageFlags)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr PipelineStageFlags -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @PipelineStageFlags ((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 -> PipelineStageFlags -> IO ())
-> Vector PipelineStageFlags -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: PipelineStageFlags
e -> Ptr PipelineStageFlags -> PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr PipelineStageFlags
pPWaitDstStageMask' Ptr PipelineStageFlags -> Int -> Ptr PipelineStageFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineStageFlags) (PipelineStageFlags
e)) (Vector PipelineStageFlags
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 PipelineStageFlags) -> Ptr PipelineStageFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr PipelineStageFlags)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr PipelineStageFlags))) (Ptr PipelineStageFlags
pPWaitDstStageMask')
    Ptr (Ptr CommandBuffer_T)
pPCommandBuffers' <- ((Ptr (Ptr CommandBuffer_T) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr CommandBuffer_T))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Ptr CommandBuffer_T) -> IO b) -> IO b)
 -> ContT b IO (Ptr (Ptr CommandBuffer_T)))
-> ((Ptr (Ptr CommandBuffer_T) -> IO b) -> IO b)
-> ContT b IO (Ptr (Ptr CommandBuffer_T))
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr (Ptr CommandBuffer_T) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @(Ptr CommandBuffer_T) ((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 -> Ptr CommandBuffer_T -> IO ())
-> Vector (Ptr CommandBuffer_T) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Ptr CommandBuffer_T
e -> Ptr (Ptr CommandBuffer_T) -> Ptr CommandBuffer_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr (Ptr CommandBuffer_T)
pPCommandBuffers' Ptr (Ptr CommandBuffer_T) -> Int -> Ptr (Ptr CommandBuffer_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CommandBuffer_T)) (Ptr CommandBuffer_T
e)) (Vector (Ptr CommandBuffer_T)
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 (Ptr CommandBuffer_T))
-> Ptr (Ptr CommandBuffer_T) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr (Ptr CommandBuffer_T))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (Ptr CommandBuffer_T)))) (Ptr (Ptr CommandBuffer_T)
pPCommandBuffers')
    Ptr Semaphore
pPSignalSemaphores' <- ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore))
-> ((Ptr Semaphore -> IO b) -> IO b) -> ContT b IO (Ptr Semaphore)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Semaphore -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Semaphore ((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 -> Semaphore -> IO ()) -> Vector Semaphore -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Semaphore
e -> Ptr Semaphore -> Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Semaphore
pPSignalSemaphores' Ptr Semaphore -> Int -> Ptr Semaphore
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore) (Semaphore
e)) (Vector Semaphore
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 Semaphore) -> Ptr Semaphore -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr Semaphore))) (Ptr Semaphore
pPSignalSemaphores')
    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 SubmitInfo es, PeekChain es) => FromCStruct (SubmitInfo es) where
  peekCStruct :: Ptr (SubmitInfo es) -> IO (SubmitInfo es)
peekCStruct p :: Ptr (SubmitInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (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 (Ptr () -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr Ptr ()
pNext)
    "queueFamilyIndex" ::: Word32
waitSemaphoreCount <- Ptr ("queueFamilyIndex" ::: Word32)
-> IO ("queueFamilyIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr ("queueFamilyIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
    Ptr Semaphore
pWaitSemaphores <- Ptr (Ptr Semaphore) -> IO (Ptr Semaphore)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Semaphore) ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr (Ptr Semaphore)))
    Vector Semaphore
pWaitSemaphores' <- Int -> (Int -> IO Semaphore) -> IO (Vector Semaphore)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("queueFamilyIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "queueFamilyIndex" ::: Word32
waitSemaphoreCount) (\i :: Int
i -> Ptr Semaphore -> IO Semaphore
forall a. Storable a => Ptr a -> IO a
peek @Semaphore ((Ptr Semaphore
pWaitSemaphores Ptr Semaphore -> Int -> Ptr Semaphore
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore)))
    Ptr PipelineStageFlags
pWaitDstStageMask <- Ptr (Ptr PipelineStageFlags) -> IO (Ptr PipelineStageFlags)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PipelineStageFlags) ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr PipelineStageFlags)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr PipelineStageFlags)))
    Vector PipelineStageFlags
pWaitDstStageMask' <- Int
-> (Int -> IO PipelineStageFlags) -> IO (Vector PipelineStageFlags)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("queueFamilyIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "queueFamilyIndex" ::: Word32
waitSemaphoreCount) (\i :: Int
i -> Ptr PipelineStageFlags -> IO PipelineStageFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineStageFlags ((Ptr PipelineStageFlags
pWaitDstStageMask Ptr PipelineStageFlags -> Int -> Ptr PipelineStageFlags
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineStageFlags)))
    "queueFamilyIndex" ::: Word32
commandBufferCount <- Ptr ("queueFamilyIndex" ::: Word32)
-> IO ("queueFamilyIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr ("queueFamilyIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr Word32))
    Ptr (Ptr CommandBuffer_T)
pCommandBuffers <- Ptr (Ptr (Ptr CommandBuffer_T)) -> IO (Ptr (Ptr CommandBuffer_T))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr (Ptr CommandBuffer_T)) ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr (Ptr CommandBuffer_T))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr (Ptr (Ptr CommandBuffer_T))))
    Vector (Ptr CommandBuffer_T)
pCommandBuffers' <- Int
-> (Int -> IO (Ptr CommandBuffer_T))
-> IO (Vector (Ptr CommandBuffer_T))
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("queueFamilyIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "queueFamilyIndex" ::: Word32
commandBufferCount) (\i :: Int
i -> Ptr (Ptr CommandBuffer_T) -> IO (Ptr CommandBuffer_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr CommandBuffer_T) ((Ptr (Ptr CommandBuffer_T)
pCommandBuffers Ptr (Ptr CommandBuffer_T) -> Int -> Ptr (Ptr CommandBuffer_T)
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr (Ptr CommandBuffer_T))))
    "queueFamilyIndex" ::: Word32
signalSemaphoreCount <- Ptr ("queueFamilyIndex" ::: Word32)
-> IO ("queueFamilyIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr ("queueFamilyIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr Word32))
    Ptr Semaphore
pSignalSemaphores <- Ptr (Ptr Semaphore) -> IO (Ptr Semaphore)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Semaphore) ((Ptr (SubmitInfo es)
p Ptr (SubmitInfo es) -> Int -> Ptr (Ptr Semaphore)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr Semaphore)))
    Vector Semaphore
pSignalSemaphores' <- Int -> (Int -> IO Semaphore) -> IO (Vector Semaphore)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("queueFamilyIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "queueFamilyIndex" ::: Word32
signalSemaphoreCount) (\i :: Int
i -> Ptr Semaphore -> IO Semaphore
forall a. Storable a => Ptr a -> IO a
peek @Semaphore ((Ptr Semaphore
pSignalSemaphores Ptr Semaphore -> Int -> Ptr Semaphore
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Semaphore)))
    SubmitInfo es -> IO (SubmitInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SubmitInfo es -> IO (SubmitInfo es))
-> SubmitInfo es -> IO (SubmitInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> Vector Semaphore
-> Vector PipelineStageFlags
-> Vector (Ptr CommandBuffer_T)
-> Vector Semaphore
-> SubmitInfo es
forall (es :: [*]).
Chain es
-> Vector Semaphore
-> Vector PipelineStageFlags
-> Vector (Ptr CommandBuffer_T)
-> Vector Semaphore
-> SubmitInfo es
SubmitInfo
             Chain es
next Vector Semaphore
pWaitSemaphores' Vector PipelineStageFlags
pWaitDstStageMask' Vector (Ptr CommandBuffer_T)
pCommandBuffers' Vector Semaphore
pSignalSemaphores'

instance es ~ '[] => Zero (SubmitInfo es) where
  zero :: SubmitInfo es
zero = Chain es
-> Vector Semaphore
-> Vector PipelineStageFlags
-> Vector (Ptr CommandBuffer_T)
-> Vector Semaphore
-> SubmitInfo es
forall (es :: [*]).
Chain es
-> Vector Semaphore
-> Vector PipelineStageFlags
-> Vector (Ptr CommandBuffer_T)
-> Vector Semaphore
-> SubmitInfo es
SubmitInfo
           ()
           Vector Semaphore
forall a. Monoid a => a
mempty
           Vector PipelineStageFlags
forall a. Monoid a => a
mempty
           Vector (Ptr CommandBuffer_T)
forall a. Monoid a => a
mempty
           Vector Semaphore
forall a. Monoid a => a
mempty