{-# 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
createDeferredOperationKHR :: forall io
                            . (MonadIO io)
                           => 
                              Device
                           -> 
                              
                              
                              ("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)
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 ()
destroyDeferredOperationKHR :: forall io
                             . (MonadIO io)
                            => 
                               Device
                            -> 
                               DeferredOperationKHR
                            -> 
                               
                               
                               ("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
getDeferredOperationMaxConcurrencyKHR :: forall io
                                       . (MonadIO io)
                                      => 
                                         
                                         
                                         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
getDeferredOperationResultKHR :: forall io
                               . (MonadIO io)
                              => 
                                 
                                 
                                 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
deferredOperationJoinKHR :: forall io
                          . (MonadIO io)
                         => 
                            Device
                         -> 
                            
                            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)
data DeferredOperationInfoKHR = DeferredOperationInfoKHR
  { 
    
    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
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"
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"