{-# language CPP #-}
-- No documentation found for Chapter "Fence"
module Vulkan.Core10.Fence  ( createFence
                            , withFence
                            , destroyFence
                            , resetFences
                            , getFenceStatus
                            , waitForFences
                            , waitForFencesSafe
                            , FenceCreateInfo(..)
                            , Fence(..)
                            , FenceCreateFlagBits(..)
                            , FenceCreateFlags
                            ) where

import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
import Foreign.Marshal.Alloc (allocaBytes)
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 (nullPtr)
import Foreign.Ptr (plusPtr)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Zero (Zero(..))
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.Word (Word64)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.Core10.FundamentalTypes (boolToBool32)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.FundamentalTypes (Bool32)
import Vulkan.Core10.FundamentalTypes (Bool32(..))
import Vulkan.CStruct.Extends (Chain)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkCreateFence))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyFence))
import Vulkan.Dynamic (DeviceCmds(pVkGetFenceStatus))
import Vulkan.Dynamic (DeviceCmds(pVkResetFences))
import Vulkan.Dynamic (DeviceCmds(pVkWaitForFences))
import Vulkan.Core10.Handles (Device_T)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_external_fence (ExportFenceCreateInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_external_fence_win32 (ExportFenceWin32HandleInfoKHR)
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.Core10.Enums.FenceCreateFlagBits (FenceCreateFlags)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_FENCE_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Handles (Fence(..))
import Vulkan.Core10.Enums.FenceCreateFlagBits (FenceCreateFlagBits(..))
import Vulkan.Core10.Enums.FenceCreateFlagBits (FenceCreateFlags)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreateFence
  :: FunPtr (Ptr Device_T -> Ptr (SomeStruct FenceCreateInfo) -> Ptr AllocationCallbacks -> Ptr Fence -> IO Result) -> Ptr Device_T -> Ptr (SomeStruct FenceCreateInfo) -> Ptr AllocationCallbacks -> Ptr Fence -> IO Result

-- | vkCreateFence - Create a new fence object
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCreateFence-device-parameter# @device@ /must/ be a valid
--     'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkCreateFence-pCreateInfo-parameter# @pCreateInfo@ /must/ be a
--     valid pointer to a valid 'FenceCreateInfo' structure
--
-- -   #VUID-vkCreateFence-pAllocator-parameter# If @pAllocator@ is not
--     @NULL@, @pAllocator@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   #VUID-vkCreateFence-pFence-parameter# @pFence@ /must/ be a valid
--     pointer to a 'Vulkan.Core10.Handles.Fence' handle
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Fence',
-- 'FenceCreateInfo'
createFence :: forall a io
             . (Extendss FenceCreateInfo a, PokeChain a, MonadIO io)
            => -- | @device@ is the logical device that creates the fence.
               Device
            -> -- | @pCreateInfo@ is a pointer to a 'FenceCreateInfo' structure containing
               -- information about how the fence is to be created.
               (FenceCreateInfo a)
            -> -- | @pAllocator@ controls host memory allocation as described in the
               -- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation>
               -- chapter.
               ("allocator" ::: Maybe AllocationCallbacks)
            -> io (Fence)
createFence :: Device
-> FenceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Fence
createFence Device
device FenceCreateInfo a
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = IO Fence -> io Fence
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Fence -> io Fence)
-> (ContT Fence IO Fence -> IO Fence)
-> ContT Fence IO Fence
-> io Fence
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Fence IO Fence -> IO Fence
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Fence IO Fence -> io Fence)
-> ContT Fence IO Fence -> io Fence
forall a b. (a -> b) -> a -> b
$ do
  let vkCreateFencePtr :: FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkCreateFencePtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pFence" ::: Ptr Fence)
      -> IO Result)
pVkCreateFence (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT Fence IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Fence IO ()) -> IO () -> ContT Fence IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkCreateFencePtr FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pFence" ::: Ptr Fence)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr 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 String
"" String
"The function pointer for vkCreateFence is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreateFence' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFence" ::: Ptr Fence)
-> IO Result
vkCreateFence' = FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFence" ::: Ptr Fence)
-> IO Result
mkVkCreateFence FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkCreateFencePtr
  Ptr (FenceCreateInfo a)
pCreateInfo <- ((Ptr (FenceCreateInfo a) -> IO Fence) -> IO Fence)
-> ContT Fence IO (Ptr (FenceCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (FenceCreateInfo a) -> IO Fence) -> IO Fence)
 -> ContT Fence IO (Ptr (FenceCreateInfo a)))
-> ((Ptr (FenceCreateInfo a) -> IO Fence) -> IO Fence)
-> ContT Fence IO (Ptr (FenceCreateInfo a))
forall a b. (a -> b) -> a -> b
$ FenceCreateInfo a
-> (Ptr (FenceCreateInfo a) -> IO Fence) -> IO Fence
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (FenceCreateInfo a
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
    Just AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
 -> IO Fence)
-> ContT Fence 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 Fence)
  -> IO Fence)
 -> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
    -> IO Fence)
-> ContT Fence IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO Fence)
-> IO Fence
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pFence" ::: Ptr Fence
pPFence <- ((("pFence" ::: Ptr Fence) -> IO Fence) -> IO Fence)
-> ContT Fence IO ("pFence" ::: Ptr Fence)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pFence" ::: Ptr Fence) -> IO Fence) -> IO Fence)
 -> ContT Fence IO ("pFence" ::: Ptr Fence))
-> ((("pFence" ::: Ptr Fence) -> IO Fence) -> IO Fence)
-> ContT Fence IO ("pFence" ::: Ptr Fence)
forall a b. (a -> b) -> a -> b
$ IO ("pFence" ::: Ptr Fence)
-> (("pFence" ::: Ptr Fence) -> IO ())
-> (("pFence" ::: Ptr Fence) -> IO Fence)
-> IO Fence
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pFence" ::: Ptr Fence)
forall a. Int -> IO (Ptr a)
callocBytes @Fence Int
8) ("pFence" ::: Ptr Fence) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT Fence IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Fence IO Result)
-> IO Result -> ContT Fence IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreateFence" (Ptr Device_T
-> ("pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pFence" ::: Ptr Fence)
-> IO Result
vkCreateFence' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Ptr (FenceCreateInfo a)
-> "pCreateInfo" ::: Ptr (SomeStruct FenceCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (FenceCreateInfo a)
pCreateInfo) "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pFence" ::: Ptr Fence
pPFence))
  IO () -> ContT Fence IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Fence IO ()) -> IO () -> ContT Fence 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))
  Fence
pFence <- IO Fence -> ContT Fence IO Fence
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Fence -> ContT Fence IO Fence)
-> IO Fence -> ContT Fence IO Fence
forall a b. (a -> b) -> a -> b
$ ("pFence" ::: Ptr Fence) -> IO Fence
forall a. Storable a => Ptr a -> IO a
peek @Fence "pFence" ::: Ptr Fence
pPFence
  Fence -> ContT Fence IO Fence
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Fence -> ContT Fence IO Fence) -> Fence -> ContT Fence IO Fence
forall a b. (a -> b) -> a -> b
$ (Fence
pFence)

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createFence' and 'destroyFence'
--
-- To ensure that 'destroyFence' is always called: pass
-- 'Control.Exception.bracket' (or the allocate function from your
-- favourite resource management library) as the last argument.
-- To just extract the pair pass '(,)' as the last argument.
--
withFence :: forall a io r . (Extendss FenceCreateInfo a, PokeChain a, MonadIO io) => Device -> FenceCreateInfo a -> Maybe AllocationCallbacks -> (io Fence -> (Fence -> io ()) -> r) -> r
withFence :: Device
-> FenceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io Fence -> (Fence -> io ()) -> r)
-> r
withFence Device
device FenceCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator io Fence -> (Fence -> io ()) -> r
b =
  io Fence -> (Fence -> io ()) -> r
b (Device
-> FenceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Fence
forall (a :: [*]) (io :: * -> *).
(Extendss FenceCreateInfo a, PokeChain a, MonadIO io) =>
Device
-> FenceCreateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io Fence
createFence Device
device FenceCreateInfo a
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(Fence
o0) -> Device
-> Fence -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> Fence -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyFence Device
device Fence
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)


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

-- | vkDestroyFence - Destroy a fence object
--
-- == Valid Usage
--
-- -   #VUID-vkDestroyFence-fence-01120# All
--     <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#devsandqueues-submission queue submission>
--     commands that refer to @fence@ /must/ have completed execution
--
-- -   #VUID-vkDestroyFence-fence-01121# If
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @fence@ was created, a compatible set of callbacks
--     /must/ be provided here
--
-- -   #VUID-vkDestroyFence-fence-01122# If no
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @fence@ was created, @pAllocator@ /must/ be @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkDestroyFence-device-parameter# @device@ /must/ be a valid
--     'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkDestroyFence-fence-parameter# If @fence@ is not
--     'Vulkan.Core10.APIConstants.NULL_HANDLE', @fence@ /must/ be a valid
--     'Vulkan.Core10.Handles.Fence' handle
--
-- -   #VUID-vkDestroyFence-pAllocator-parameter# If @pAllocator@ is not
--     @NULL@, @pAllocator@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   #VUID-vkDestroyFence-fence-parent# If @fence@ is a valid handle, it
--     /must/ have been created, allocated, or retrieved from @device@
--
-- == Host Synchronization
--
-- -   Host access to @fence@ /must/ be externally synchronized
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks',
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Fence'
destroyFence :: forall io
              . (MonadIO io)
             => -- | @device@ is the logical device that destroys the fence.
                Device
             -> -- | @fence@ is the handle of the fence to destroy.
                Fence
             -> -- | @pAllocator@ controls host memory allocation as described in the
                -- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                -- chapter.
                ("allocator" ::: Maybe AllocationCallbacks)
             -> io ()
destroyFence :: Device
-> Fence -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyFence Device
device Fence
fence "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 vkDestroyFencePtr :: FunPtr
  (Ptr Device_T
   -> Fence -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyFencePtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> Fence -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
pVkDestroyFence (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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
   -> Fence -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyFencePtr FunPtr
  (Ptr Device_T
   -> Fence -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> FunPtr
     (Ptr Device_T
      -> Fence -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> Fence -> ("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 String
"" String
"The function pointer for vkDestroyFence is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyFence' :: Ptr Device_T
-> Fence -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyFence' = FunPtr
  (Ptr Device_T
   -> Fence -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
-> Ptr Device_T
-> Fence
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyFence FunPtr
  (Ptr Device_T
   -> Fence -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ())
vkDestroyFencePtr
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
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 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
$ String -> IO () -> IO ()
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkDestroyFence" (Ptr Device_T
-> Fence -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
vkDestroyFence' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Fence
fence) "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" mkVkResetFences
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr Fence -> IO Result) -> Ptr Device_T -> Word32 -> Ptr Fence -> IO Result

-- | vkResetFences - Resets one or more fence objects
--
-- = Description
--
-- If any member of @pFences@ currently has its
-- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#synchronization-fences-importing payload imported>
-- with temporary permanence, that fence’s prior permanent payload is first
-- restored. The remaining operations described therefore operate on the
-- restored payload.
--
-- When 'resetFences' is executed on the host, it defines a /fence unsignal
-- operation/ for each fence, which resets the fence to the unsignaled
-- state.
--
-- If any member of @pFences@ is already in the unsignaled state when
-- 'resetFences' is executed, then 'resetFences' has no effect on that
-- fence.
--
-- == Valid Usage
--
-- -   #VUID-vkResetFences-pFences-01123# Each element of @pFences@ /must/
--     not be currently associated with any queue command that has not yet
--     completed execution on that queue
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkResetFences-device-parameter# @device@ /must/ be a valid
--     'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkResetFences-pFences-parameter# @pFences@ /must/ be a valid
--     pointer to an array of @fenceCount@ valid
--     'Vulkan.Core10.Handles.Fence' handles
--
-- -   #VUID-vkResetFences-fenceCount-arraylength# @fenceCount@ /must/ be
--     greater than @0@
--
-- -   #VUID-vkResetFences-pFences-parent# Each element of @pFences@ /must/
--     have been created, allocated, or retrieved from @device@
--
-- == Host Synchronization
--
-- -   Host access to each member of @pFences@ /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_DEVICE_MEMORY'
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Fence'
resetFences :: forall io
             . (MonadIO io)
            => -- | @device@ is the logical device that owns the fences.
               Device
            -> -- | @pFences@ is a pointer to an array of fence handles to reset.
               ("fences" ::: Vector Fence)
            -> io ()
resetFences :: Device -> ("fences" ::: Vector Fence) -> io ()
resetFences Device
device "fences" ::: Vector Fence
fences = 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 vkResetFencesPtr :: FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkResetFencesPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("fenceCount" ::: Word32)
      -> ("pFence" ::: Ptr Fence)
      -> IO Result)
pVkResetFences (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  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
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkResetFencesPtr FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("fenceCount" ::: Word32)
      -> ("pFence" ::: Ptr Fence)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr 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 String
"" String
"The function pointer for vkResetFences is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkResetFences' :: Ptr Device_T
-> ("fenceCount" ::: Word32)
-> ("pFence" ::: Ptr Fence)
-> IO Result
vkResetFences' = FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
-> Ptr Device_T
-> ("fenceCount" ::: Word32)
-> ("pFence" ::: Ptr Fence)
-> IO Result
mkVkResetFences FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> IO Result)
vkResetFencesPtr
  "pFence" ::: Ptr Fence
pPFences <- ((("pFence" ::: Ptr Fence) -> IO ()) -> IO ())
-> ContT () IO ("pFence" ::: Ptr Fence)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pFence" ::: Ptr Fence) -> IO ()) -> IO ())
 -> ContT () IO ("pFence" ::: Ptr Fence))
-> ((("pFence" ::: Ptr Fence) -> IO ()) -> IO ())
-> ContT () IO ("pFence" ::: Ptr Fence)
forall a b. (a -> b) -> a -> b
$ Int -> (("pFence" ::: Ptr Fence) -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Fence ((("fences" ::: Vector Fence) -> Int
forall a. Vector a -> Int
Data.Vector.length ("fences" ::: Vector Fence
fences)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8)
  IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Fence -> IO ()) -> ("fences" ::: Vector Fence) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Fence
e -> ("pFence" ::: Ptr Fence) -> Fence -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pFence" ::: Ptr Fence
pPFences ("pFence" ::: Ptr Fence) -> Int -> "pFence" ::: Ptr Fence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Fence) (Fence
e)) ("fences" ::: Vector Fence
fences)
  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
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkResetFences" (Ptr Device_T
-> ("fenceCount" ::: Word32)
-> ("pFence" ::: Ptr Fence)
-> IO Result
vkResetFences' (Device -> Ptr Device_T
deviceHandle (Device
device)) ((Int -> "fenceCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("fences" ::: Vector Fence) -> Int
forall a. Vector a -> Int
Data.Vector.length (("fences" ::: Vector Fence) -> Int)
-> ("fences" ::: Vector Fence) -> Int
forall a b. (a -> b) -> a -> b
$ ("fences" ::: Vector Fence
fences)) :: Word32)) ("pFence" ::: Ptr Fence
pPFences))
  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" mkVkGetFenceStatus
  :: FunPtr (Ptr Device_T -> Fence -> IO Result) -> Ptr Device_T -> Fence -> IO Result

-- | vkGetFenceStatus - Return the status of a fence
--
-- = Description
--
-- Upon success, 'getFenceStatus' returns the status of the fence object,
-- with the following return codes:
--
-- +------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+
-- | Status                                         | Meaning                                                                                                                |
-- +================================================+========================================================================================================================+
-- | 'Vulkan.Core10.Enums.Result.SUCCESS'           | The fence specified by @fence@ is signaled.                                                                            |
-- +------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+
-- | 'Vulkan.Core10.Enums.Result.NOT_READY'         | The fence specified by @fence@ is unsignaled.                                                                          |
-- +------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+
-- | 'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST' | The device has been lost. See                                                                                          |
-- |                                                | <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#devsandqueues-lost-device Lost Device>. |
-- +------------------------------------------------+------------------------------------------------------------------------------------------------------------------------+
--
-- Fence Object Status Codes
--
-- If a
-- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#devsandqueues-submission queue submission>
-- command is pending execution, then the value returned by this command
-- /may/ immediately be out of date.
--
-- If the device has been lost (see
-- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#devsandqueues-lost-device Lost Device>),
-- 'getFenceStatus' /may/ return any of the above status codes. If the
-- device has been lost and 'getFenceStatus' is called repeatedly, it will
-- eventually return either 'Vulkan.Core10.Enums.Result.SUCCESS' or
-- 'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'.
--
-- == 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'
--
-- [<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
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.Handles.Device', 'Vulkan.Core10.Handles.Fence'
getFenceStatus :: forall io
                . (MonadIO io)
               => -- | @device@ is the logical device that owns the fence.
                  --
                  -- #VUID-vkGetFenceStatus-device-parameter# @device@ /must/ be a valid
                  -- 'Vulkan.Core10.Handles.Device' handle
                  Device
               -> -- | @fence@ is the handle of the fence to query.
                  --
                  -- #VUID-vkGetFenceStatus-fence-parameter# @fence@ /must/ be a valid
                  -- 'Vulkan.Core10.Handles.Fence' handle
                  --
                  -- #VUID-vkGetFenceStatus-fence-parent# @fence@ /must/ have been created,
                  -- allocated, or retrieved from @device@
                  Fence
               -> io (Result)
getFenceStatus :: Device -> Fence -> io Result
getFenceStatus Device
device Fence
fence = 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 vkGetFenceStatusPtr :: FunPtr (Ptr Device_T -> Fence -> IO Result)
vkGetFenceStatusPtr = DeviceCmds -> FunPtr (Ptr Device_T -> Fence -> IO Result)
pVkGetFenceStatus (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> Fence -> IO Result)
vkGetFenceStatusPtr FunPtr (Ptr Device_T -> Fence -> IO Result)
-> FunPtr (Ptr Device_T -> Fence -> IO Result) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> 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 String
"" String
"The function pointer for vkGetFenceStatus is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetFenceStatus' :: Ptr Device_T -> Fence -> IO Result
vkGetFenceStatus' = FunPtr (Ptr Device_T -> Fence -> IO Result)
-> Ptr Device_T -> Fence -> IO Result
mkVkGetFenceStatus FunPtr (Ptr Device_T -> Fence -> IO Result)
vkGetFenceStatusPtr
  Result
r <- String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetFenceStatus" (Ptr Device_T -> Fence -> IO Result
vkGetFenceStatus' (Device -> Ptr Device_T
deviceHandle (Device
device)) (Fence
fence))
  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)


foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkWaitForFencesUnsafe
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr Fence -> Bool32 -> Word64 -> IO Result) -> Ptr Device_T -> Word32 -> Ptr Fence -> Bool32 -> Word64 -> IO Result

foreign import ccall
  "dynamic" mkVkWaitForFencesSafe
  :: FunPtr (Ptr Device_T -> Word32 -> Ptr Fence -> Bool32 -> Word64 -> IO Result) -> Ptr Device_T -> Word32 -> Ptr Fence -> Bool32 -> Word64 -> IO Result

-- | waitForFences with selectable safeness
waitForFencesSafeOrUnsafe :: forall io
                           . (MonadIO io)
                          => (FunPtr (Ptr Device_T -> Word32 -> Ptr Fence -> Bool32 -> Word64 -> IO Result) -> Ptr Device_T -> Word32 -> Ptr Fence -> Bool32 -> Word64 -> IO Result)
                          -> -- | @device@ is the logical device that owns the fences.
                             Device
                          -> -- | @pFences@ is a pointer to an array of @fenceCount@ fence handles.
                             ("fences" ::: Vector Fence)
                          -> -- | @waitAll@ is the condition that /must/ be satisfied to successfully
                             -- unblock the wait. If @waitAll@ is 'Vulkan.Core10.FundamentalTypes.TRUE',
                             -- then the condition is that all fences in @pFences@ are signaled.
                             -- Otherwise, the condition is that at least one fence in @pFences@ is
                             -- signaled.
                             ("waitAll" ::: Bool)
                          -> -- | @timeout@ is the timeout period in units of nanoseconds. @timeout@ is
                             -- adjusted to the closest value allowed by the implementation-dependent
                             -- timeout accuracy, which /may/ be substantially longer than one
                             -- nanosecond, and /may/ be longer than the requested period.
                             ("timeout" ::: Word64)
                          -> io (Result)
waitForFencesSafeOrUnsafe :: (FunPtr
   (Ptr Device_T
    -> ("fenceCount" ::: Word32)
    -> ("pFence" ::: Ptr Fence)
    -> Bool32
    -> Word64
    -> IO Result)
 -> Ptr Device_T
 -> ("fenceCount" ::: Word32)
 -> ("pFence" ::: Ptr Fence)
 -> Bool32
 -> Word64
 -> IO Result)
-> Device
-> ("fences" ::: Vector Fence)
-> Bool
-> Word64
-> io Result
waitForFencesSafeOrUnsafe FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> Bool32
   -> Word64
   -> IO Result)
-> Ptr Device_T
-> ("fenceCount" ::: Word32)
-> ("pFence" ::: Ptr Fence)
-> Bool32
-> Word64
-> IO Result
mkVkWaitForFences Device
device "fences" ::: Vector Fence
fences Bool
waitAll Word64
timeout = IO Result -> io Result
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Result -> io Result)
-> (ContT Result IO Result -> IO Result)
-> ContT Result IO Result
-> io Result
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Result IO Result -> IO Result
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Result IO Result -> io Result)
-> ContT Result IO Result -> io Result
forall a b. (a -> b) -> a -> b
$ do
  let vkWaitForFencesPtr :: FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> Bool32
   -> Word64
   -> IO Result)
vkWaitForFencesPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("fenceCount" ::: Word32)
      -> ("pFence" ::: Ptr Fence)
      -> Bool32
      -> Word64
      -> IO Result)
pVkWaitForFences (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> Bool32
   -> Word64
   -> IO Result)
vkWaitForFencesPtr FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> Bool32
   -> Word64
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("fenceCount" ::: Word32)
      -> ("pFence" ::: Ptr Fence)
      -> Bool32
      -> Word64
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> Bool32
   -> Word64
   -> 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 String
"" String
"The function pointer for vkWaitForFences is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkWaitForFences' :: Ptr Device_T
-> ("fenceCount" ::: Word32)
-> ("pFence" ::: Ptr Fence)
-> Bool32
-> Word64
-> IO Result
vkWaitForFences' = FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> Bool32
   -> Word64
   -> IO Result)
-> Ptr Device_T
-> ("fenceCount" ::: Word32)
-> ("pFence" ::: Ptr Fence)
-> Bool32
-> Word64
-> IO Result
mkVkWaitForFences FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> Bool32
   -> Word64
   -> IO Result)
vkWaitForFencesPtr
  "pFence" ::: Ptr Fence
pPFences <- ((("pFence" ::: Ptr Fence) -> IO Result) -> IO Result)
-> ContT Result IO ("pFence" ::: Ptr Fence)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pFence" ::: Ptr Fence) -> IO Result) -> IO Result)
 -> ContT Result IO ("pFence" ::: Ptr Fence))
-> ((("pFence" ::: Ptr Fence) -> IO Result) -> IO Result)
-> ContT Result IO ("pFence" ::: Ptr Fence)
forall a b. (a -> b) -> a -> b
$ Int -> (("pFence" ::: Ptr Fence) -> IO Result) -> IO Result
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @Fence ((("fences" ::: Vector Fence) -> Int
forall a. Vector a -> Int
Data.Vector.length ("fences" ::: Vector Fence
fences)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8)
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Fence -> IO ()) -> ("fences" ::: Vector Fence) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i Fence
e -> ("pFence" ::: Ptr Fence) -> Fence -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pFence" ::: Ptr Fence
pPFences ("pFence" ::: Ptr Fence) -> Int -> "pFence" ::: Ptr Fence
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Fence) (Fence
e)) ("fences" ::: Vector Fence
fences)
  Result
r <- IO Result -> ContT Result IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Result IO Result)
-> IO Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkWaitForFences" (Ptr Device_T
-> ("fenceCount" ::: Word32)
-> ("pFence" ::: Ptr Fence)
-> Bool32
-> Word64
-> IO Result
vkWaitForFences' (Device -> Ptr Device_T
deviceHandle (Device
device)) ((Int -> "fenceCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("fences" ::: Vector Fence) -> Int
forall a. Vector a -> Int
Data.Vector.length (("fences" ::: Vector Fence) -> Int)
-> ("fences" ::: Vector Fence) -> Int
forall a b. (a -> b) -> a -> b
$ ("fences" ::: Vector Fence
fences)) :: Word32)) ("pFence" ::: Ptr Fence
pPFences) (Bool -> Bool32
boolToBool32 (Bool
waitAll)) (Word64
timeout))
  IO () -> ContT Result IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Result IO ()) -> IO () -> ContT Result IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
  Result -> ContT Result IO Result
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Result -> ContT Result IO Result)
-> Result -> ContT Result IO Result
forall a b. (a -> b) -> a -> b
$ (Result
r)

-- | vkWaitForFences - Wait for one or more fences to become signaled
--
-- = Description
--
-- If the condition is satisfied when 'waitForFences' is called, then
-- 'waitForFences' returns immediately. If the condition is not satisfied
-- at the time 'waitForFences' is called, then 'waitForFences' will block
-- and wait until the condition is satisfied or the @timeout@ has expired,
-- whichever is sooner.
--
-- If @timeout@ is zero, then 'waitForFences' does not wait, but simply
-- returns the current state of the fences.
-- 'Vulkan.Core10.Enums.Result.TIMEOUT' will be returned in this case if
-- the condition is not satisfied, even though no actual wait was
-- performed.
--
-- If the condition is satisfied before the @timeout@ has expired,
-- 'waitForFences' returns 'Vulkan.Core10.Enums.Result.SUCCESS'. Otherwise,
-- 'waitForFences' returns 'Vulkan.Core10.Enums.Result.TIMEOUT' after the
-- @timeout@ has expired.
--
-- If device loss occurs (see
-- <https://www.khronos.org/registry/vulkan/specs/1.3-extensions/html/vkspec.html#devsandqueues-lost-device Lost Device>)
-- before the timeout has expired, 'waitForFences' /must/ return in finite
-- time with either 'Vulkan.Core10.Enums.Result.SUCCESS' or
-- 'Vulkan.Core10.Enums.Result.ERROR_DEVICE_LOST'.
--
-- Note
--
-- While we guarantee that 'waitForFences' /must/ return in finite time, no
-- guarantees are made that it returns immediately upon device loss.
-- However, the client can reasonably expect that the delay will be on the
-- order of seconds and that calling 'waitForFences' will not result in a
-- permanently (or seemingly permanently) dead process.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkWaitForFences-device-parameter# @device@ /must/ be a valid
--     'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkWaitForFences-pFences-parameter# @pFences@ /must/ be a valid
--     pointer to an array of @fenceCount@ valid
--     'Vulkan.Core10.Handles.Fence' handles
--
-- -   #VUID-vkWaitForFences-fenceCount-arraylength# @fenceCount@ /must/ be
--     greater than @0@
--
-- -   #VUID-vkWaitForFences-pFences-parent# Each element of @pFences@
--     /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.TIMEOUT'
--
-- [<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
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.FundamentalTypes.Bool32', 'Vulkan.Core10.Handles.Device',
-- 'Vulkan.Core10.Handles.Fence'
waitForFences :: forall io
               . (MonadIO io)
              => -- | @device@ is the logical device that owns the fences.
                 Device
              -> -- | @pFences@ is a pointer to an array of @fenceCount@ fence handles.
                 ("fences" ::: Vector Fence)
              -> -- | @waitAll@ is the condition that /must/ be satisfied to successfully
                 -- unblock the wait. If @waitAll@ is 'Vulkan.Core10.FundamentalTypes.TRUE',
                 -- then the condition is that all fences in @pFences@ are signaled.
                 -- Otherwise, the condition is that at least one fence in @pFences@ is
                 -- signaled.
                 ("waitAll" ::: Bool)
              -> -- | @timeout@ is the timeout period in units of nanoseconds. @timeout@ is
                 -- adjusted to the closest value allowed by the implementation-dependent
                 -- timeout accuracy, which /may/ be substantially longer than one
                 -- nanosecond, and /may/ be longer than the requested period.
                 ("timeout" ::: Word64)
              -> io (Result)
waitForFences :: Device
-> ("fences" ::: Vector Fence) -> Bool -> Word64 -> io Result
waitForFences = (FunPtr
   (Ptr Device_T
    -> ("fenceCount" ::: Word32)
    -> ("pFence" ::: Ptr Fence)
    -> Bool32
    -> Word64
    -> IO Result)
 -> Ptr Device_T
 -> ("fenceCount" ::: Word32)
 -> ("pFence" ::: Ptr Fence)
 -> Bool32
 -> Word64
 -> IO Result)
-> Device
-> ("fences" ::: Vector Fence)
-> Bool
-> Word64
-> io Result
forall (io :: * -> *).
MonadIO io =>
(FunPtr
   (Ptr Device_T
    -> ("fenceCount" ::: Word32)
    -> ("pFence" ::: Ptr Fence)
    -> Bool32
    -> Word64
    -> IO Result)
 -> Ptr Device_T
 -> ("fenceCount" ::: Word32)
 -> ("pFence" ::: Ptr Fence)
 -> Bool32
 -> Word64
 -> IO Result)
-> Device
-> ("fences" ::: Vector Fence)
-> Bool
-> Word64
-> io Result
waitForFencesSafeOrUnsafe FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> Bool32
   -> Word64
   -> IO Result)
-> Ptr Device_T
-> ("fenceCount" ::: Word32)
-> ("pFence" ::: Ptr Fence)
-> Bool32
-> Word64
-> IO Result
mkVkWaitForFencesUnsafe

-- | A variant of 'waitForFences' which makes a *safe* FFI call
waitForFencesSafe :: forall io
                   . (MonadIO io)
                  => -- | @device@ is the logical device that owns the fences.
                     Device
                  -> -- | @pFences@ is a pointer to an array of @fenceCount@ fence handles.
                     ("fences" ::: Vector Fence)
                  -> -- | @waitAll@ is the condition that /must/ be satisfied to successfully
                     -- unblock the wait. If @waitAll@ is 'Vulkan.Core10.FundamentalTypes.TRUE',
                     -- then the condition is that all fences in @pFences@ are signaled.
                     -- Otherwise, the condition is that at least one fence in @pFences@ is
                     -- signaled.
                     ("waitAll" ::: Bool)
                  -> -- | @timeout@ is the timeout period in units of nanoseconds. @timeout@ is
                     -- adjusted to the closest value allowed by the implementation-dependent
                     -- timeout accuracy, which /may/ be substantially longer than one
                     -- nanosecond, and /may/ be longer than the requested period.
                     ("timeout" ::: Word64)
                  -> io (Result)
waitForFencesSafe :: Device
-> ("fences" ::: Vector Fence) -> Bool -> Word64 -> io Result
waitForFencesSafe = (FunPtr
   (Ptr Device_T
    -> ("fenceCount" ::: Word32)
    -> ("pFence" ::: Ptr Fence)
    -> Bool32
    -> Word64
    -> IO Result)
 -> Ptr Device_T
 -> ("fenceCount" ::: Word32)
 -> ("pFence" ::: Ptr Fence)
 -> Bool32
 -> Word64
 -> IO Result)
-> Device
-> ("fences" ::: Vector Fence)
-> Bool
-> Word64
-> io Result
forall (io :: * -> *).
MonadIO io =>
(FunPtr
   (Ptr Device_T
    -> ("fenceCount" ::: Word32)
    -> ("pFence" ::: Ptr Fence)
    -> Bool32
    -> Word64
    -> IO Result)
 -> Ptr Device_T
 -> ("fenceCount" ::: Word32)
 -> ("pFence" ::: Ptr Fence)
 -> Bool32
 -> Word64
 -> IO Result)
-> Device
-> ("fences" ::: Vector Fence)
-> Bool
-> Word64
-> io Result
waitForFencesSafeOrUnsafe FunPtr
  (Ptr Device_T
   -> ("fenceCount" ::: Word32)
   -> ("pFence" ::: Ptr Fence)
   -> Bool32
   -> Word64
   -> IO Result)
-> Ptr Device_T
-> ("fenceCount" ::: Word32)
-> ("pFence" ::: Ptr Fence)
-> Bool32
-> Word64
-> IO Result
mkVkWaitForFencesSafe


-- | VkFenceCreateInfo - Structure specifying parameters of a newly created
-- fence
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkFenceCreateInfo-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_FENCE_CREATE_INFO'
--
-- -   #VUID-VkFenceCreateInfo-pNext-pNext# 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.Core11.Promoted_From_VK_KHR_external_fence.ExportFenceCreateInfo'
--     or
--     'Vulkan.Extensions.VK_KHR_external_fence_win32.ExportFenceWin32HandleInfoKHR'
--
-- -   #VUID-VkFenceCreateInfo-sType-unique# The @sType@ value of each
--     struct in the @pNext@ chain /must/ be unique
--
-- -   #VUID-VkFenceCreateInfo-flags-parameter# @flags@ /must/ be a valid
--     combination of
--     'Vulkan.Core10.Enums.FenceCreateFlagBits.FenceCreateFlagBits' values
--
-- = See Also
--
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#VK_VERSION_1_0 VK_VERSION_1_0>,
-- 'Vulkan.Core10.Enums.FenceCreateFlagBits.FenceCreateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'createFence'
data FenceCreateInfo (es :: [Type]) = FenceCreateInfo
  { -- | @pNext@ is @NULL@ or a pointer to a structure extending this structure.
    FenceCreateInfo es -> Chain es
next :: Chain es
  , -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.FenceCreateFlagBits.FenceCreateFlagBits' specifying
    -- the initial state and behavior of the fence.
    FenceCreateInfo es -> FenceCreateFlags
flags :: FenceCreateFlags
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (FenceCreateInfo (es :: [Type]))
#endif
deriving instance Show (Chain es) => Show (FenceCreateInfo es)

instance Extensible FenceCreateInfo where
  extensibleTypeName :: String
extensibleTypeName = String
"FenceCreateInfo"
  setNext :: FenceCreateInfo ds -> Chain es -> FenceCreateInfo es
setNext FenceCreateInfo{Chain ds
FenceCreateFlags
flags :: FenceCreateFlags
next :: Chain ds
$sel:flags:FenceCreateInfo :: forall (es :: [*]). FenceCreateInfo es -> FenceCreateFlags
$sel:next:FenceCreateInfo :: forall (es :: [*]). FenceCreateInfo es -> Chain es
..} Chain es
next' = FenceCreateInfo :: forall (es :: [*]).
Chain es -> FenceCreateFlags -> FenceCreateInfo es
FenceCreateInfo{$sel:next:FenceCreateInfo :: Chain es
next = Chain es
next', FenceCreateFlags
flags :: FenceCreateFlags
$sel:flags:FenceCreateInfo :: FenceCreateFlags
..}
  getNext :: FenceCreateInfo es -> Chain es
getNext FenceCreateInfo{Chain es
FenceCreateFlags
flags :: FenceCreateFlags
next :: Chain es
$sel:flags:FenceCreateInfo :: forall (es :: [*]). FenceCreateInfo es -> FenceCreateFlags
$sel:next:FenceCreateInfo :: forall (es :: [*]). FenceCreateInfo es -> Chain es
..} = Chain es
next
  extends :: forall e b proxy. Typeable e => proxy e -> (Extends FenceCreateInfo e => b) -> Maybe b
  extends :: proxy e -> (Extends FenceCreateInfo e => b) -> Maybe b
extends proxy e
_ Extends FenceCreateInfo e => b
f
    | Just e :~: ExportFenceWin32HandleInfoKHR
Refl <- (Typeable e, Typeable ExportFenceWin32HandleInfoKHR) =>
Maybe (e :~: ExportFenceWin32HandleInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExportFenceWin32HandleInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends FenceCreateInfo e => b
f
    | Just e :~: ExportFenceCreateInfo
Refl <- (Typeable e, Typeable ExportFenceCreateInfo) =>
Maybe (e :~: ExportFenceCreateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExportFenceCreateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends FenceCreateInfo e => b
f
    | Bool
otherwise = Maybe b
forall a. Maybe a
Nothing

instance (Extendss FenceCreateInfo es, PokeChain es) => ToCStruct (FenceCreateInfo es) where
  withCStruct :: FenceCreateInfo es -> (Ptr (FenceCreateInfo es) -> IO b) -> IO b
withCStruct FenceCreateInfo es
x Ptr (FenceCreateInfo es) -> IO b
f = Int -> (Ptr (FenceCreateInfo es) -> IO b) -> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
24 ((Ptr (FenceCreateInfo es) -> IO b) -> IO b)
-> (Ptr (FenceCreateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \Ptr (FenceCreateInfo es)
p -> Ptr (FenceCreateInfo es) -> FenceCreateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (FenceCreateInfo es)
p FenceCreateInfo es
x (Ptr (FenceCreateInfo es) -> IO b
f Ptr (FenceCreateInfo es)
p)
  pokeCStruct :: Ptr (FenceCreateInfo es) -> FenceCreateInfo es -> IO b -> IO b
pokeCStruct Ptr (FenceCreateInfo es)
p FenceCreateInfo{Chain es
FenceCreateFlags
flags :: FenceCreateFlags
next :: Chain es
$sel:flags:FenceCreateInfo :: forall (es :: [*]). FenceCreateInfo es -> FenceCreateFlags
$sel:next:FenceCreateInfo :: forall (es :: [*]). FenceCreateInfo es -> Chain es
..} 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 (FenceCreateInfo es)
p Ptr (FenceCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FENCE_CREATE_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 (FenceCreateInfo es)
p Ptr (FenceCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext''
    IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr FenceCreateFlags -> FenceCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FenceCreateInfo es)
p Ptr (FenceCreateInfo es) -> Int -> Ptr FenceCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr FenceCreateFlags)) (FenceCreateFlags
flags)
    IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
  cStructSize :: Int
cStructSize = Int
24
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: Ptr (FenceCreateInfo es) -> IO b -> IO b
pokeZeroCStruct Ptr (FenceCreateInfo es)
p 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 (FenceCreateInfo es)
p Ptr (FenceCreateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_FENCE_CREATE_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 (FenceCreateInfo es)
p Ptr (FenceCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) Ptr ()
pNext'
    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 FenceCreateInfo es, PeekChain es) => FromCStruct (FenceCreateInfo es) where
  peekCStruct :: Ptr (FenceCreateInfo es) -> IO (FenceCreateInfo es)
peekCStruct Ptr (FenceCreateInfo es)
p = do
    Ptr ()
pNext <- Ptr (Ptr ()) -> IO (Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (FenceCreateInfo es)
p Ptr (FenceCreateInfo es) -> Int -> Ptr (Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
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)
    FenceCreateFlags
flags <- Ptr FenceCreateFlags -> IO FenceCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @FenceCreateFlags ((Ptr (FenceCreateInfo es)
p Ptr (FenceCreateInfo es) -> Int -> Ptr FenceCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr FenceCreateFlags))
    FenceCreateInfo es -> IO (FenceCreateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FenceCreateInfo es -> IO (FenceCreateInfo es))
-> FenceCreateInfo es -> IO (FenceCreateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es -> FenceCreateFlags -> FenceCreateInfo es
forall (es :: [*]).
Chain es -> FenceCreateFlags -> FenceCreateInfo es
FenceCreateInfo
             Chain es
next FenceCreateFlags
flags

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