{-# language CPP #-}
module Vulkan.Extensions.VK_KHR_deferred_host_operations  ( createDeferredOperationKHR
                                                          , withDeferredOperationKHR
                                                          , destroyDeferredOperationKHR
                                                          , getDeferredOperationMaxConcurrencyKHR
                                                          , getDeferredOperationResultKHR
                                                          , deferredOperationJoinKHR
                                                          , DeferredOperationInfoKHR(..)
                                                          , KHR_DEFERRED_HOST_OPERATIONS_SPEC_VERSION
                                                          , pattern KHR_DEFERRED_HOST_OPERATIONS_SPEC_VERSION
                                                          , KHR_DEFERRED_HOST_OPERATIONS_EXTENSION_NAME
                                                          , pattern KHR_DEFERRED_HOST_OPERATIONS_EXTENSION_NAME
                                                          , DeferredOperationKHR(..)
                                                          ) where

import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
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 (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
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 Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Extensions.Handles (DeferredOperationKHR)
import Vulkan.Extensions.Handles (DeferredOperationKHR(..))
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkCreateDeferredOperationKHR))
import Vulkan.Dynamic (DeviceCmds(pVkDeferredOperationJoinKHR))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyDeferredOperationKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeferredOperationMaxConcurrencyKHR))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeferredOperationResultKHR))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_DEFERRED_OPERATION_INFO_KHR))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Extensions.Handles (DeferredOperationKHR(..))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateDeferredOperationKHR
  :: FunPtr (Ptr Device_T -> Ptr AllocationCallbacks -> Ptr DeferredOperationKHR -> IO Result) -> Ptr Device_T -> Ptr AllocationCallbacks -> Ptr DeferredOperationKHR -> IO Result

-- | vkCreateDeferredOperationKHR - Create a deferred operation handle
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   @pDeferredOperation@ /must/ be a valid pointer to a
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' handle
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Handles.Device'
createDeferredOperationKHR :: forall io
                            . (MonadIO io)
                           => -- | @device@ is the device which owns @operation@.
                              Device
                           -> -- | @pAllocator@ controls host memory allocation as described in the
                              -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                              -- chapter.
                              ("allocator" ::: Maybe AllocationCallbacks)
                           -> io (DeferredOperationKHR)
createDeferredOperationKHR :: Device
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io DeferredOperationKHR
createDeferredOperationKHR device :: Device
device allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO DeferredOperationKHR -> io DeferredOperationKHR
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeferredOperationKHR -> io DeferredOperationKHR)
-> (ContT DeferredOperationKHR IO DeferredOperationKHR
    -> IO DeferredOperationKHR)
-> ContT DeferredOperationKHR IO DeferredOperationKHR
-> io DeferredOperationKHR
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT DeferredOperationKHR IO DeferredOperationKHR
-> IO DeferredOperationKHR
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT DeferredOperationKHR IO DeferredOperationKHR
 -> io DeferredOperationKHR)
-> ContT DeferredOperationKHR IO DeferredOperationKHR
-> io DeferredOperationKHR
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateDeferredOperationKHRPtr :: FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
   -> IO Result)
vkCreateDeferredOperationKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
      -> IO Result)
pVkCreateDeferredOperationKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT DeferredOperationKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DeferredOperationKHR IO ())
-> IO () -> ContT DeferredOperationKHR IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
   -> IO Result)
vkCreateDeferredOperationKHRPtr FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
   -> 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 vkCreateDeferredOperationKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateDeferredOperationKHR' :: Ptr Device_T
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
-> IO Result
vkCreateDeferredOperationKHR' = FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
   -> IO Result)
-> Ptr Device_T
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
-> IO Result
mkVkCreateDeferredOperationKHR FunPtr
  (Ptr Device_T
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
   -> IO Result)
vkCreateDeferredOperationKHRPtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT
     DeferredOperationKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks)
  -> IO DeferredOperationKHR)
 -> IO DeferredOperationKHR)
-> ContT
     DeferredOperationKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO DeferredOperationKHR)
  -> IO DeferredOperationKHR)
 -> ContT
      DeferredOperationKHR IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks)
     -> IO DeferredOperationKHR)
    -> IO DeferredOperationKHR)
-> ContT
     DeferredOperationKHR IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks)
    -> IO DeferredOperationKHR)
-> IO DeferredOperationKHR
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pDeferredOperation" ::: Ptr DeferredOperationKHR
pPDeferredOperation <- ((("pDeferredOperation" ::: Ptr DeferredOperationKHR)
  -> IO DeferredOperationKHR)
 -> IO DeferredOperationKHR)
-> ContT
     DeferredOperationKHR
     IO
     ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDeferredOperation" ::: Ptr DeferredOperationKHR)
   -> IO DeferredOperationKHR)
  -> IO DeferredOperationKHR)
 -> ContT
      DeferredOperationKHR
      IO
      ("pDeferredOperation" ::: Ptr DeferredOperationKHR))
-> ((("pDeferredOperation" ::: Ptr DeferredOperationKHR)
     -> IO DeferredOperationKHR)
    -> IO DeferredOperationKHR)
-> ContT
     DeferredOperationKHR
     IO
     ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
forall a b. (a -> b) -> a -> b
$ IO ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
-> (("pDeferredOperation" ::: Ptr DeferredOperationKHR) -> IO ())
-> (("pDeferredOperation" ::: Ptr DeferredOperationKHR)
    -> IO DeferredOperationKHR)
-> IO DeferredOperationKHR
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
forall a. Int -> IO (Ptr a)
callocBytes @DeferredOperationKHR 8) ("pDeferredOperation" ::: Ptr DeferredOperationKHR) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT DeferredOperationKHR IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT DeferredOperationKHR IO Result)
-> IO Result -> ContT DeferredOperationKHR IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
-> IO Result
vkCreateDeferredOperationKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pDeferredOperation" ::: Ptr DeferredOperationKHR
pPDeferredOperation)
  IO () -> ContT DeferredOperationKHR IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DeferredOperationKHR IO ())
-> IO () -> ContT DeferredOperationKHR 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))
  DeferredOperationKHR
pDeferredOperation <- IO DeferredOperationKHR
-> ContT DeferredOperationKHR IO DeferredOperationKHR
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO DeferredOperationKHR
 -> ContT DeferredOperationKHR IO DeferredOperationKHR)
-> IO DeferredOperationKHR
-> ContT DeferredOperationKHR IO DeferredOperationKHR
forall a b. (a -> b) -> a -> b
$ ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
-> IO DeferredOperationKHR
forall a. Storable a => Ptr a -> IO a
peek @DeferredOperationKHR "pDeferredOperation" ::: Ptr DeferredOperationKHR
pPDeferredOperation
  DeferredOperationKHR
-> ContT DeferredOperationKHR IO DeferredOperationKHR
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeferredOperationKHR
 -> ContT DeferredOperationKHR IO DeferredOperationKHR)
-> DeferredOperationKHR
-> ContT DeferredOperationKHR IO DeferredOperationKHR
forall a b. (a -> b) -> a -> b
$ (DeferredOperationKHR
pDeferredOperation)

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


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

-- | vkDestroyDeferredOperationKHR - Destroy a deferred operation handle
--
-- == Valid Usage
--
-- -   If 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @operation@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   If no 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @operation@ was created, @pAllocator@ /must/ be @NULL@
--
-- -   @operation@ /must/ be completed
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   If @operation@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @operation@ /must/ be a valid
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' handle
--
-- -   If @pAllocator@ is not @NULL@, @pAllocator@ /must/ be a valid
--     pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   If @operation@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Host Synchronization
--
-- -   Host access to @operation@ /must/ be externally synchronized
--
-- = See Also
--
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Handles.Device'
destroyDeferredOperationKHR :: forall io
                             . (MonadIO io)
                            => -- | @device@ is the device which owns @operation@.
                               Device
                            -> -- | @operation@ is the completed operation to be destroyed.
                               DeferredOperationKHR
                            -> -- | @pAllocator@ controls host memory allocation as described in the
                               -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                               -- chapter.
                               ("allocator" ::: Maybe AllocationCallbacks)
                            -> io ()
destroyDeferredOperationKHR :: Device
-> DeferredOperationKHR
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyDeferredOperationKHR device :: Device
device operation :: DeferredOperationKHR
operation allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
  let vkDestroyDeferredOperationKHRPtr :: FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyDeferredOperationKHRPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroyDeferredOperationKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyDeferredOperationKHRPtr FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> DeferredOperationKHR
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
forall a. FunPtr a
nullFunPtr) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    IOException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (IOException -> IO ()) -> IOException -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError Maybe Handle
forall a. Maybe a
Nothing IOErrorType
InvalidArgument "" "The function pointer for vkDestroyDeferredOperationKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyDeferredOperationKHR' :: Ptr Device_T
-> DeferredOperationKHR
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyDeferredOperationKHR' = FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> Ptr Device_T
-> DeferredOperationKHR
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyDeferredOperationKHR FunPtr
  (Ptr Device_T
   -> DeferredOperationKHR
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyDeferredOperationKHRPtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
 -> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> DeferredOperationKHR
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyDeferredOperationKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DeferredOperationKHR
operation) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator
  () -> ContT () IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> ContT () IO ()) -> () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ()


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

-- | vkGetDeferredOperationMaxConcurrencyKHR - Query the maximum concurrency
-- on a deferred operation
--
-- = Description
--
-- The returned value is the maximum number of threads that can usefully
-- execute a deferred operation concurrently, reported for the state of the
-- deferred operation at the point this command is called. This value is
-- intended to be used to better schedule work onto available threads.
-- Applications /can/ join any number of threads to the deferred operation
-- and expect it to eventually complete, though excessive joins /may/
-- return 'Vulkan.Core10.Enums.Result.THREAD_DONE_KHR' immediately,
-- performing no useful work.
--
-- If @operation@ is complete, 'getDeferredOperationMaxConcurrencyKHR'
-- returns zero.
--
-- If @operation@ is currently joined to any threads, the value returned by
-- this command /may/ immediately be out of date.
--
-- If @operation@ is pending, implementations /must/ not return zero unless
-- at least one thread is currently executing 'deferredOperationJoinKHR' on
-- @operation@. If there are such threads, the implementation /should/
-- return an estimate of the number of additional threads which it could
-- profitably use.
--
-- Implementations /may/ return 232-1 to indicate that the maximum
-- concurrency is unknown and cannot be easily derived. Implementations
-- /may/ return values larger than the maximum concurrency available on the
-- host CPU. In these situations, an application /should/ clamp the return
-- value rather than oversubscribing the machine.
--
-- Note
--
-- The recommended usage pattern for applications is to query this value
-- once, after deferral, and schedule no more than the specified number of
-- threads to join the operation. Each time a joined thread receives
-- 'Vulkan.Core10.Enums.Result.THREAD_IDLE_KHR', the application should
-- schedule an additional join at some point in the future, but is not
-- required to do so.
--
-- == Valid Usage (Implicit)
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Handles.Device'
getDeferredOperationMaxConcurrencyKHR :: forall io
                                       . (MonadIO io)
                                      => -- | @device@ is the device which owns @operation@.
                                         --
                                         -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                         Device
                                      -> -- | @operation@ is the deferred operation to be queried.
                                         --
                                         -- @operation@ /must/ be a valid
                                         -- 'Vulkan.Extensions.Handles.DeferredOperationKHR' handle
                                         --
                                         -- @operation@ /must/ have been created, allocated, or retrieved from
                                         -- @device@
                                         DeferredOperationKHR
                                      -> io (Word32)
getDeferredOperationMaxConcurrencyKHR :: Device -> DeferredOperationKHR -> io Word32
getDeferredOperationMaxConcurrencyKHR device :: Device
device operation :: DeferredOperationKHR
operation = IO Word32 -> io Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> io Word32) -> IO Word32 -> io Word32
forall a b. (a -> b) -> a -> b
$ do
  let vkGetDeferredOperationMaxConcurrencyKHRPtr :: FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Word32)
vkGetDeferredOperationMaxConcurrencyKHRPtr = DeviceCmds
-> FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Word32)
pVkGetDeferredOperationMaxConcurrencyKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Word32)
vkGetDeferredOperationMaxConcurrencyKHRPtr FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Word32)
-> FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Word32)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Word32)
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 vkGetDeferredOperationMaxConcurrencyKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeferredOperationMaxConcurrencyKHR' :: Ptr Device_T -> DeferredOperationKHR -> IO Word32
vkGetDeferredOperationMaxConcurrencyKHR' = FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Word32)
-> Ptr Device_T -> DeferredOperationKHR -> IO Word32
mkVkGetDeferredOperationMaxConcurrencyKHR FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Word32)
vkGetDeferredOperationMaxConcurrencyKHRPtr
  Word32
r <- Ptr Device_T -> DeferredOperationKHR -> IO Word32
vkGetDeferredOperationMaxConcurrencyKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DeferredOperationKHR
operation)
  Word32 -> IO Word32
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word32 -> IO Word32) -> Word32 -> IO Word32
forall a b. (a -> b) -> a -> b
$ (Word32
r)


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

-- | vkGetDeferredOperationResultKHR - Query the result of a deferred
-- operation
--
-- = Description
--
-- If the deferred operation is pending, 'getDeferredOperationResultKHR'
-- returns 'Vulkan.Core10.Enums.Result.NOT_READY'.
--
-- If no command has been deferred on @operation@,
-- 'getDeferredOperationResultKHR' returns
-- 'Vulkan.Core10.Enums.Result.SUCCESS'.
--
-- Otherwise, it returns the result of the previous deferred operation.
-- This value /must/ be one of the 'Vulkan.Core10.Enums.Result.Result'
-- values which could have been returned by the original command if the
-- operation had not been deferred.
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.NOT_READY'
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Handles.Device'
getDeferredOperationResultKHR :: forall io
                               . (MonadIO io)
                              => -- | @device@ is the device which owns @operation@.
                                 --
                                 -- @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
                                 Device
                              -> -- | @operation@ is the operation whose deferred result is being queried.
                                 --
                                 -- @operation@ /must/ be a valid
                                 -- 'Vulkan.Extensions.Handles.DeferredOperationKHR' handle
                                 --
                                 -- @operation@ /must/ have been created, allocated, or retrieved from
                                 -- @device@
                                 DeferredOperationKHR
                              -> io (Result)
getDeferredOperationResultKHR :: Device -> DeferredOperationKHR -> io Result
getDeferredOperationResultKHR device :: Device
device operation :: DeferredOperationKHR
operation = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result) -> IO Result -> io Result
forall a b. (a -> b) -> a -> b
$ do
  let vkGetDeferredOperationResultKHRPtr :: FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
vkGetDeferredOperationResultKHRPtr = DeviceCmds
-> FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
pVkGetDeferredOperationResultKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
vkGetDeferredOperationResultKHRPtr FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
-> FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> DeferredOperationKHR -> 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 vkGetDeferredOperationResultKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetDeferredOperationResultKHR' :: Ptr Device_T -> DeferredOperationKHR -> IO Result
vkGetDeferredOperationResultKHR' = FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
-> Ptr Device_T -> DeferredOperationKHR -> IO Result
mkVkGetDeferredOperationResultKHR FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
vkGetDeferredOperationResultKHRPtr
  Result
r <- Ptr Device_T -> DeferredOperationKHR -> IO Result
vkGetDeferredOperationResultKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DeferredOperationKHR
operation)
  Result -> IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ (Result
r)


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

-- | vkDeferredOperationJoinKHR - Assign a thread to a deferred operation
--
-- = Description
--
-- The 'deferredOperationJoinKHR' command will execute a portion of the
-- deferred operation on the calling thread.
--
-- The return value will be one of the following:
--
-- -   A return value of 'Vulkan.Core10.Enums.Result.SUCCESS' indicates
--     that @operation@ is complete. The application /should/ use
--     'getDeferredOperationResultKHR' to retrieve the result of
--     @operation@.
--
-- -   A return value of 'Vulkan.Core10.Enums.Result.THREAD_DONE_KHR'
--     indicates that the deferred operation is not complete, but there is
--     no work remaining to assign to threads. Future calls to
--     'deferredOperationJoinKHR' are not necessary and will simply harm
--     performance. This situation /may/ occur when other threads executing
--     'deferredOperationJoinKHR' are about to complete @operation@, and
--     the implementation is unable to partition the workload any further.
--
-- -   A return value of 'Vulkan.Core10.Enums.Result.THREAD_IDLE_KHR'
--     indicates that the deferred operation is not complete, and there is
--     no work for the thread to do at the time of the call. This situation
--     /may/ occur if the operation encounters a temporary reduction in
--     parallelism. By returning
--     'Vulkan.Core10.Enums.Result.THREAD_IDLE_KHR', the implementation is
--     signaling that it expects that more opportunities for parallelism
--     will emerge as execution progresses, and that future calls to
--     'deferredOperationJoinKHR' /can/ be beneficial. In the meantime, the
--     application /can/ perform other work on the calling thread.
--
-- Implementations /must/ guarantee forward progress by enforcing the
-- following invariants:
--
-- 1.  If only one thread has invoked 'deferredOperationJoinKHR' on a given
--     operation, that thread /must/ execute the operation to completion
--     and return 'Vulkan.Core10.Enums.Result.SUCCESS'.
--
-- 2.  If multiple threads have concurrently invoked
--     'deferredOperationJoinKHR' on the same operation, then at least one
--     of them /must/ complete the operation and return
--     'Vulkan.Core10.Enums.Result.SUCCESS'.
--
-- == Valid Usage (Implicit)
--
-- -   @device@ /must/ be a valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   @operation@ /must/ be a valid
--     'Vulkan.Extensions.Handles.DeferredOperationKHR' handle
--
-- -   @operation@ /must/ have been created, allocated, or retrieved from
--     @device@
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
--     -   'Vulkan.Core10.Enums.Result.THREAD_DONE_KHR'
--
--     -   'Vulkan.Core10.Enums.Result.THREAD_IDLE_KHR'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Handles.Device'
deferredOperationJoinKHR :: forall io
                          . (MonadIO io)
                         => -- | @device@ is the device which owns @operation@.
                            Device
                         -> -- | @operation@ is the deferred operation that the calling thread should
                            -- work on.
                            DeferredOperationKHR
                         -> io (Result)
deferredOperationJoinKHR :: Device -> DeferredOperationKHR -> io Result
deferredOperationJoinKHR device :: Device
device operation :: DeferredOperationKHR
operation = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result) -> IO Result -> io Result
forall a b. (a -> b) -> a -> b
$ do
  let vkDeferredOperationJoinKHRPtr :: FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
vkDeferredOperationJoinKHRPtr = DeviceCmds
-> FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
pVkDeferredOperationJoinKHR (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
vkDeferredOperationJoinKHRPtr FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
-> FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> DeferredOperationKHR -> 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 vkDeferredOperationJoinKHR is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDeferredOperationJoinKHR' :: Ptr Device_T -> DeferredOperationKHR -> IO Result
vkDeferredOperationJoinKHR' = FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
-> Ptr Device_T -> DeferredOperationKHR -> IO Result
mkVkDeferredOperationJoinKHR FunPtr (Ptr Device_T -> DeferredOperationKHR -> IO Result)
vkDeferredOperationJoinKHRPtr
  Result
r <- Ptr Device_T -> DeferredOperationKHR -> IO Result
vkDeferredOperationJoinKHR' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DeferredOperationKHR
operation)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Result -> IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> IO Result) -> Result -> IO Result
forall a b. (a -> b) -> a -> b
$ (Result
r)


-- | VkDeferredOperationInfoKHR - Deferred operation request
--
-- = Description
--
-- The application /can/ request deferral of an operation by adding this
-- structure to the argument list of a command or by providing this in the
-- @pNext@ chain of a relevant structure for an operation when the
-- corresponding command is invoked. If this structure is not present, no
-- deferral is requested. If @operationHandle@ is
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE', no deferral is requested and
-- the command proceeds as if no 'DeferredOperationInfoKHR' structure was
-- provided.
--
-- When an application requests an operation deferral, the implementation
-- /may/ defer the operation. When deferral is requested and the
-- implementation defers any operation, the implementation /must/ return
-- 'Vulkan.Core10.Enums.Result.OPERATION_DEFERRED_KHR' as the success code
-- if no errors occurred. When deferral is requested, the implementation
-- /should/ defer the operation when the workload is significant, however
-- if the implementation chooses not to defer any of the requested
-- operations and instead executes all of them immediately, the
-- implementation /must/ return
-- 'Vulkan.Core10.Enums.Result.OPERATION_NOT_DEFERRED_KHR' as the success
-- code if no errors occurred.
--
-- A deferred operation is created /complete/ with an initial result value
-- of 'Vulkan.Core10.Enums.Result.SUCCESS'. The deferred operation becomes
-- /pending/ when an operation has been successfully deferred with that
-- @operationHandle@.
--
-- A deferred operation is considered pending until the deferred operation
-- completes. A pending deferred operation becomes /complete/ when it has
-- been fully executed by one or more threads. Pending deferred operations
-- will never complete until they are /joined/ by an application thread,
-- using 'deferredOperationJoinKHR'. Applications /can/ join multiple
-- threads to the same deferred operation, enabling concurrent execution of
-- subtasks within that operation.
--
-- The application /can/ query the status of a
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR' using the
-- 'getDeferredOperationMaxConcurrencyKHR' or
-- 'getDeferredOperationResultKHR' commands.
--
-- From the perspective of other commands - parameters to the original
-- command that are externally synchronized /must/ not be accessed before
-- the deferred operation completes, and the result of the deferred
-- operation (e.g. object creation) are not considered complete until the
-- deferred operation completes.
--
-- If the deferred operation is one which creates an object (for example, a
-- pipeline object), the implementation /must/ allocate that object as it
-- normally would, and return a valid handle to the application. This
-- object is a /pending/ object, and /must/ not be used by the application
-- until the deferred operation is completed (unless otherwise specified by
-- the deferral extension). When the deferred operation is complete, the
-- application /should/ call 'getDeferredOperationResultKHR' to obtain the
-- result of the operation. If 'getDeferredOperationResultKHR' indicates
-- failure, the application /must/ destroy the pending object using an
-- appropriate command, so that the implementation has an opportunity to
-- recover the handle. The application /must/ not perform this destruction
-- until the deferred operation is complete. Construction of the pending
-- object uses the same allocator which would have been used if the
-- operation had not been deferred.
--
-- == Valid Usage
--
-- -   Any previous deferred operation that was associated with
--     @operationHandle@ /must/ be complete
--
-- == Valid Usage (Implicit)
--
-- -   @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_DEFERRED_OPERATION_INFO_KHR'
--
-- = See Also
--
-- 'Vulkan.Extensions.Handles.DeferredOperationKHR',
-- 'Vulkan.Core10.Enums.StructureType.StructureType'
data DeferredOperationInfoKHR = DeferredOperationInfoKHR
  { -- | @operationHandle@ is a handle to a tracking object to associate with the
    -- deferred operation.
    DeferredOperationInfoKHR -> DeferredOperationKHR
operationHandle :: DeferredOperationKHR }
  deriving (Typeable, DeferredOperationInfoKHR -> DeferredOperationInfoKHR -> Bool
(DeferredOperationInfoKHR -> DeferredOperationInfoKHR -> Bool)
-> (DeferredOperationInfoKHR -> DeferredOperationInfoKHR -> Bool)
-> Eq DeferredOperationInfoKHR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeferredOperationInfoKHR -> DeferredOperationInfoKHR -> Bool
$c/= :: DeferredOperationInfoKHR -> DeferredOperationInfoKHR -> Bool
== :: DeferredOperationInfoKHR -> DeferredOperationInfoKHR -> Bool
$c== :: DeferredOperationInfoKHR -> DeferredOperationInfoKHR -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeferredOperationInfoKHR)
#endif
deriving instance Show DeferredOperationInfoKHR

instance ToCStruct DeferredOperationInfoKHR where
  withCStruct :: DeferredOperationInfoKHR
-> (Ptr DeferredOperationInfoKHR -> IO b) -> IO b
withCStruct x :: DeferredOperationInfoKHR
x f :: Ptr DeferredOperationInfoKHR -> IO b
f = Int -> Int -> (Ptr DeferredOperationInfoKHR -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DeferredOperationInfoKHR -> IO b) -> IO b)
-> (Ptr DeferredOperationInfoKHR -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeferredOperationInfoKHR
p -> Ptr DeferredOperationInfoKHR
-> DeferredOperationInfoKHR -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeferredOperationInfoKHR
p DeferredOperationInfoKHR
x (Ptr DeferredOperationInfoKHR -> IO b
f Ptr DeferredOperationInfoKHR
p)
  pokeCStruct :: Ptr DeferredOperationInfoKHR
-> DeferredOperationInfoKHR -> IO b -> IO b
pokeCStruct p :: Ptr DeferredOperationInfoKHR
p DeferredOperationInfoKHR{..} f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeferredOperationInfoKHR
p Ptr DeferredOperationInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEFERRED_OPERATION_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeferredOperationInfoKHR
p Ptr DeferredOperationInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
-> DeferredOperationKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeferredOperationInfoKHR
p Ptr DeferredOperationInfoKHR
-> Int -> "pDeferredOperation" ::: Ptr DeferredOperationKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeferredOperationKHR)) (DeferredOperationKHR
operationHandle)
    IO b
f
  cStructSize :: Int
cStructSize = 24
  cStructAlignment :: Int
cStructAlignment = 8
  pokeZeroCStruct :: Ptr DeferredOperationInfoKHR -> IO b -> IO b
pokeZeroCStruct p :: Ptr DeferredOperationInfoKHR
p f :: IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeferredOperationInfoKHR
p Ptr DeferredOperationInfoKHR -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_DEFERRED_OPERATION_INFO_KHR)
    Ptr (Ptr ()) -> Ptr () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeferredOperationInfoKHR
p Ptr DeferredOperationInfoKHR -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) (Ptr ()
forall a. Ptr a
nullPtr)
    ("pDeferredOperation" ::: Ptr DeferredOperationKHR)
-> DeferredOperationKHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeferredOperationInfoKHR
p Ptr DeferredOperationInfoKHR
-> Int -> "pDeferredOperation" ::: Ptr DeferredOperationKHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeferredOperationKHR)) (DeferredOperationKHR
forall a. Zero a => a
zero)
    IO b
f

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

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

instance Zero DeferredOperationInfoKHR where
  zero :: DeferredOperationInfoKHR
zero = DeferredOperationKHR -> DeferredOperationInfoKHR
DeferredOperationInfoKHR
           DeferredOperationKHR
forall a. Zero a => a
zero


type KHR_DEFERRED_HOST_OPERATIONS_SPEC_VERSION = 3

-- No documentation found for TopLevel "VK_KHR_DEFERRED_HOST_OPERATIONS_SPEC_VERSION"
pattern KHR_DEFERRED_HOST_OPERATIONS_SPEC_VERSION :: forall a . Integral a => a
pattern $bKHR_DEFERRED_HOST_OPERATIONS_SPEC_VERSION :: a
$mKHR_DEFERRED_HOST_OPERATIONS_SPEC_VERSION :: forall r a. Integral a => a -> (Void# -> r) -> (Void# -> r) -> r
KHR_DEFERRED_HOST_OPERATIONS_SPEC_VERSION = 3


type KHR_DEFERRED_HOST_OPERATIONS_EXTENSION_NAME = "VK_KHR_deferred_host_operations"

-- No documentation found for TopLevel "VK_KHR_DEFERRED_HOST_OPERATIONS_EXTENSION_NAME"
pattern KHR_DEFERRED_HOST_OPERATIONS_EXTENSION_NAME :: forall a . (Eq a, IsString a) => a
pattern $bKHR_DEFERRED_HOST_OPERATIONS_EXTENSION_NAME :: a
$mKHR_DEFERRED_HOST_OPERATIONS_EXTENSION_NAME :: forall r a.
(Eq a, IsString a) =>
a -> (Void# -> r) -> (Void# -> r) -> r
KHR_DEFERRED_HOST_OPERATIONS_EXTENSION_NAME = "VK_KHR_deferred_host_operations"