{-# language CPP #-}
-- No documentation found for Chapter "PipelineCache"
module Vulkan.Core10.PipelineCache  ( createPipelineCache
                                    , withPipelineCache
                                    , destroyPipelineCache
                                    , getPipelineCacheData
                                    , mergePipelineCaches
                                    , PipelineCacheCreateInfo(..)
                                    , PipelineCache(..)
                                    , PipelineCacheCreateFlagBits(..)
                                    , PipelineCacheCreateFlags
                                    ) where

import Vulkan.Internal.Utils (traceAroundEvent)
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
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 Data.ByteString (packCStringLen)
import Data.Coerce (coerce)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Foreign.C.Types (CSize(..))
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.Typeable (Typeable)
import Foreign.C.Types (CChar)
import Foreign.C.Types (CSize)
import Foreign.C.Types (CSize(..))
import Foreign.C.Types (CSize(CSize))
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.Word (Word64)
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Core10.Handles (Device(Device))
import Vulkan.Dynamic (DeviceCmds(pVkCreatePipelineCache))
import Vulkan.Dynamic (DeviceCmds(pVkDestroyPipelineCache))
import Vulkan.Dynamic (DeviceCmds(pVkGetPipelineCacheData))
import Vulkan.Dynamic (DeviceCmds(pVkMergePipelineCaches))
import Vulkan.Core10.Handles (Device_T)
import Vulkan.Core10.Handles (PipelineCache)
import Vulkan.Core10.Handles (PipelineCache(..))
import Vulkan.Core10.Enums.PipelineCacheCreateFlagBits (PipelineCacheCreateFlags)
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.Core10.Enums.StructureType (StructureType)
import Vulkan.Exception (VulkanException(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_CACHE_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
import Vulkan.Core10.Handles (PipelineCache(..))
import Vulkan.Core10.Enums.PipelineCacheCreateFlagBits (PipelineCacheCreateFlagBits(..))
import Vulkan.Core10.Enums.PipelineCacheCreateFlagBits (PipelineCacheCreateFlags)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
  unsafe
#endif
  "dynamic" mkVkCreatePipelineCache
  :: FunPtr (Ptr Device_T -> Ptr PipelineCacheCreateInfo -> Ptr AllocationCallbacks -> Ptr PipelineCache -> IO Result) -> Ptr Device_T -> Ptr PipelineCacheCreateInfo -> Ptr AllocationCallbacks -> Ptr PipelineCache -> IO Result

-- | vkCreatePipelineCache - Creates a new pipeline cache
--
-- = Description
--
-- Note
--
-- Applications /can/ track and manage the total host memory size of a
-- pipeline cache object using the @pAllocator@. Applications /can/ limit
-- the amount of data retrieved from a pipeline cache object in
-- 'getPipelineCacheData'. Implementations /should/ not internally limit
-- the total number of entries added to a pipeline cache object or the
-- total host memory consumed.
--
-- Once created, a pipeline cache /can/ be passed to the
-- 'Vulkan.Core10.Pipeline.createGraphicsPipelines'
-- 'Vulkan.Extensions.VK_KHR_ray_tracing_pipeline.createRayTracingPipelinesKHR',
-- 'Vulkan.Extensions.VK_NV_ray_tracing.createRayTracingPipelinesNV', and
-- 'Vulkan.Core10.Pipeline.createComputePipelines' commands. If the
-- pipeline cache passed into these commands is not
-- 'Vulkan.Core10.APIConstants.NULL_HANDLE', the implementation will query
-- it for possible reuse opportunities and update it with new content. The
-- use of the pipeline cache object in these commands is internally
-- synchronized, and the same pipeline cache object /can/ be used in
-- multiple threads simultaneously.
--
-- If @flags@ of @pCreateInfo@ includes
-- 'Vulkan.Core10.Enums.PipelineCacheCreateFlagBits.PIPELINE_CACHE_CREATE_EXTERNALLY_SYNCHRONIZED_BIT_EXT',
-- all commands that modify the returned pipeline cache object /must/ be
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-threadingbehavior externally synchronized>.
--
-- Note
--
-- Implementations /should/ make every effort to limit any critical
-- sections to the actual accesses to the cache, which is expected to be
-- significantly shorter than the duration of the @vkCreate*Pipelines@
-- commands.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkCreatePipelineCache-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkCreatePipelineCache-pCreateInfo-parameter# @pCreateInfo@
--     /must/ be a valid pointer to a valid 'PipelineCacheCreateInfo'
--     structure
--
-- -   #VUID-vkCreatePipelineCache-pAllocator-parameter# If @pAllocator@ is
--     not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   #VUID-vkCreatePipelineCache-pPipelineCache-parameter#
--     @pPipelineCache@ /must/ be a valid pointer to a
--     'Vulkan.Core10.Handles.PipelineCache' 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.PipelineCache',
-- 'PipelineCacheCreateInfo'
createPipelineCache :: forall io
                     . (MonadIO io)
                    => -- | @device@ is the logical device that creates the pipeline cache object.
                       Device
                    -> -- | @pCreateInfo@ is a pointer to a 'PipelineCacheCreateInfo' structure
                       -- containing initial parameters for the pipeline cache object.
                       PipelineCacheCreateInfo
                    -> -- | @pAllocator@ controls host memory allocation as described in the
                       -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                       -- chapter.
                       ("allocator" ::: Maybe AllocationCallbacks)
                    -> io (PipelineCache)
createPipelineCache :: Device
-> PipelineCacheCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PipelineCache
createPipelineCache Device
device PipelineCacheCreateInfo
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = IO PipelineCache -> io PipelineCache
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PipelineCache -> io PipelineCache)
-> (ContT PipelineCache IO PipelineCache -> IO PipelineCache)
-> ContT PipelineCache IO PipelineCache
-> io PipelineCache
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT PipelineCache IO PipelineCache -> IO PipelineCache
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT PipelineCache IO PipelineCache -> io PipelineCache)
-> ContT PipelineCache IO PipelineCache -> io PipelineCache
forall a b. (a -> b) -> a -> b
$ do
  let vkCreatePipelineCachePtr :: FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
vkCreatePipelineCachePtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pPipelineCache" ::: Ptr PipelineCache)
      -> IO Result)
pVkCreatePipelineCache (case Device
device of Device{DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds :: DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT PipelineCache IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PipelineCache IO ())
-> IO () -> ContT PipelineCache 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 PipelineCacheCreateInfo)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
vkCreatePipelineCachePtr FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> ("pPipelineCache" ::: Ptr PipelineCache)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> 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 vkCreatePipelineCache is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkCreatePipelineCache' :: Ptr Device_T
-> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelineCache" ::: Ptr PipelineCache)
-> IO Result
vkCreatePipelineCache' = FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
-> Ptr Device_T
-> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelineCache" ::: Ptr PipelineCache)
-> IO Result
mkVkCreatePipelineCache FunPtr
  (Ptr Device_T
   -> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
vkCreatePipelineCachePtr
  "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
pCreateInfo <- ((("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
  -> IO PipelineCache)
 -> IO PipelineCache)
-> ContT
     PipelineCache IO ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
   -> IO PipelineCache)
  -> IO PipelineCache)
 -> ContT
      PipelineCache IO ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo))
-> ((("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
     -> IO PipelineCache)
    -> IO PipelineCache)
-> ContT
     PipelineCache IO ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
forall a b. (a -> b) -> a -> b
$ PipelineCacheCreateInfo
-> (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
    -> IO PipelineCache)
-> IO PipelineCache
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PipelineCacheCreateInfo
createInfo)
  "pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
    "allocator" ::: Maybe AllocationCallbacks
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT
     PipelineCache 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 PipelineCache)
 -> IO PipelineCache)
-> ContT
     PipelineCache 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 PipelineCache)
  -> IO PipelineCache)
 -> ContT
      PipelineCache IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks)
     -> IO PipelineCache)
    -> IO PipelineCache)
-> ContT
     PipelineCache IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO PipelineCache)
-> IO PipelineCache
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
  "pPipelineCache" ::: Ptr PipelineCache
pPPipelineCache <- ((("pPipelineCache" ::: Ptr PipelineCache) -> IO PipelineCache)
 -> IO PipelineCache)
-> ContT PipelineCache IO ("pPipelineCache" ::: Ptr PipelineCache)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPipelineCache" ::: Ptr PipelineCache) -> IO PipelineCache)
  -> IO PipelineCache)
 -> ContT PipelineCache IO ("pPipelineCache" ::: Ptr PipelineCache))
-> ((("pPipelineCache" ::: Ptr PipelineCache) -> IO PipelineCache)
    -> IO PipelineCache)
-> ContT PipelineCache IO ("pPipelineCache" ::: Ptr PipelineCache)
forall a b. (a -> b) -> a -> b
$ IO ("pPipelineCache" ::: Ptr PipelineCache)
-> (("pPipelineCache" ::: Ptr PipelineCache) -> IO ())
-> (("pPipelineCache" ::: Ptr PipelineCache) -> IO PipelineCache)
-> IO PipelineCache
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pPipelineCache" ::: Ptr PipelineCache)
forall a. Int -> IO (Ptr a)
callocBytes @PipelineCache Int
8) ("pPipelineCache" ::: Ptr PipelineCache) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT PipelineCache IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT PipelineCache IO Result)
-> IO Result -> ContT PipelineCache IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkCreatePipelineCache" (Ptr Device_T
-> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelineCache" ::: Ptr PipelineCache)
-> IO Result
vkCreatePipelineCache' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
pCreateInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pPipelineCache" ::: Ptr PipelineCache
pPPipelineCache))
  IO () -> ContT PipelineCache IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PipelineCache IO ())
-> IO () -> ContT PipelineCache 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))
  PipelineCache
pPipelineCache <- IO PipelineCache -> ContT PipelineCache IO PipelineCache
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO PipelineCache -> ContT PipelineCache IO PipelineCache)
-> IO PipelineCache -> ContT PipelineCache IO PipelineCache
forall a b. (a -> b) -> a -> b
$ ("pPipelineCache" ::: Ptr PipelineCache) -> IO PipelineCache
forall a. Storable a => Ptr a -> IO a
peek @PipelineCache "pPipelineCache" ::: Ptr PipelineCache
pPPipelineCache
  PipelineCache -> ContT PipelineCache IO PipelineCache
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineCache -> ContT PipelineCache IO PipelineCache)
-> PipelineCache -> ContT PipelineCache IO PipelineCache
forall a b. (a -> b) -> a -> b
$ (PipelineCache
pPipelineCache)

-- | A convenience wrapper to make a compatible pair of calls to
-- 'createPipelineCache' and 'destroyPipelineCache'
--
-- To ensure that 'destroyPipelineCache' 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.
--
withPipelineCache :: forall io r . MonadIO io => Device -> PipelineCacheCreateInfo -> Maybe AllocationCallbacks -> (io PipelineCache -> (PipelineCache -> io ()) -> r) -> r
withPipelineCache :: Device
-> PipelineCacheCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io PipelineCache -> (PipelineCache -> io ()) -> r)
-> r
withPipelineCache Device
device PipelineCacheCreateInfo
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator io PipelineCache -> (PipelineCache -> io ()) -> r
b =
  io PipelineCache -> (PipelineCache -> io ()) -> r
b (Device
-> PipelineCacheCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PipelineCache
forall (io :: * -> *).
MonadIO io =>
Device
-> PipelineCacheCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PipelineCache
createPipelineCache Device
device PipelineCacheCreateInfo
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
    (\(PipelineCache
o0) -> Device
-> PipelineCache
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> PipelineCache
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyPipelineCache Device
device PipelineCache
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)


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

-- | vkDestroyPipelineCache - Destroy a pipeline cache object
--
-- == Valid Usage
--
-- -   #VUID-vkDestroyPipelineCache-pipelineCache-00771# If
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @pipelineCache@ was created, a compatible set of
--     callbacks /must/ be provided here
--
-- -   #VUID-vkDestroyPipelineCache-pipelineCache-00772# If no
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' were
--     provided when @pipelineCache@ was created, @pAllocator@ /must/ be
--     @NULL@
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkDestroyPipelineCache-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkDestroyPipelineCache-pipelineCache-parameter# If
--     @pipelineCache@ is not 'Vulkan.Core10.APIConstants.NULL_HANDLE',
--     @pipelineCache@ /must/ be a valid
--     'Vulkan.Core10.Handles.PipelineCache' handle
--
-- -   #VUID-vkDestroyPipelineCache-pAllocator-parameter# If @pAllocator@
--     is not @NULL@, @pAllocator@ /must/ be a valid pointer to a valid
--     'Vulkan.Core10.AllocationCallbacks.AllocationCallbacks' structure
--
-- -   #VUID-vkDestroyPipelineCache-pipelineCache-parent# If
--     @pipelineCache@ is a valid handle, it /must/ have been created,
--     allocated, or retrieved from @device@
--
-- == Host Synchronization
--
-- -   Host access to @pipelineCache@ /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.PipelineCache'
destroyPipelineCache :: forall io
                      . (MonadIO io)
                     => -- | @device@ is the logical device that destroys the pipeline cache object.
                        Device
                     -> -- | @pipelineCache@ is the handle of the pipeline cache to destroy.
                        PipelineCache
                     -> -- | @pAllocator@ controls host memory allocation as described in the
                        -- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#memory-allocation Memory Allocation>
                        -- chapter.
                        ("allocator" ::: Maybe AllocationCallbacks)
                     -> io ()
destroyPipelineCache :: Device
-> PipelineCache
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyPipelineCache Device
device PipelineCache
pipelineCache "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 vkDestroyPipelineCachePtr :: FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyPipelineCachePtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
pVkDestroyPipelineCache (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
   -> PipelineCache
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyPipelineCachePtr FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("pAllocator" ::: Ptr AllocationCallbacks)
      -> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("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 vkDestroyPipelineCache is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkDestroyPipelineCache' :: Ptr Device_T
-> PipelineCache
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyPipelineCache' = FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
-> Ptr Device_T
-> PipelineCache
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkDestroyPipelineCache FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pAllocator" ::: Ptr AllocationCallbacks)
   -> IO ())
vkDestroyPipelineCachePtr
  "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
"vkDestroyPipelineCache" (Ptr Device_T
-> PipelineCache
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkDestroyPipelineCache' (Device -> Ptr Device_T
deviceHandle (Device
device)) (PipelineCache
pipelineCache) "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" mkVkGetPipelineCacheData
  :: FunPtr (Ptr Device_T -> PipelineCache -> Ptr CSize -> Ptr () -> IO Result) -> Ptr Device_T -> PipelineCache -> Ptr CSize -> Ptr () -> IO Result

-- | vkGetPipelineCacheData - Get the data store from a pipeline cache
--
-- = Description
--
-- If @pData@ is @NULL@, then the maximum size of the data that /can/ be
-- retrieved from the pipeline cache, in bytes, is returned in @pDataSize@.
-- Otherwise, @pDataSize@ /must/ point to a variable set by the user to the
-- size of the buffer, in bytes, pointed to by @pData@, and on return the
-- variable is overwritten with the amount of data actually written to
-- @pData@. If @pDataSize@ is less than the maximum size that /can/ be
-- retrieved by the pipeline cache, at most @pDataSize@ bytes will be
-- written to @pData@, and 'Vulkan.Core10.Enums.Result.INCOMPLETE' will be
-- returned instead of 'Vulkan.Core10.Enums.Result.SUCCESS', to indicate
-- that not all of the pipeline cache was returned.
--
-- Any data written to @pData@ is valid and /can/ be provided as the
-- @pInitialData@ member of the 'PipelineCacheCreateInfo' structure passed
-- to 'createPipelineCache'.
--
-- Two calls to 'getPipelineCacheData' with the same parameters /must/
-- retrieve the same data unless a command that modifies the contents of
-- the cache is called between them.
--
-- The initial bytes written to @pData@ /must/ be a header as described in
-- the
-- <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#pipelines-cache-header Pipeline Cache Header>
-- section.
--
-- If @pDataSize@ is less than what is necessary to store this header,
-- nothing will be written to @pData@ and zero will be written to
-- @pDataSize@.
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkGetPipelineCacheData-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkGetPipelineCacheData-pipelineCache-parameter#
--     @pipelineCache@ /must/ be a valid
--     'Vulkan.Core10.Handles.PipelineCache' handle
--
-- -   #VUID-vkGetPipelineCacheData-pDataSize-parameter# @pDataSize@ /must/
--     be a valid pointer to a @size_t@ value
--
-- -   #VUID-vkGetPipelineCacheData-pData-parameter# If the value
--     referenced by @pDataSize@ is not @0@, and @pData@ is not @NULL@,
--     @pData@ /must/ be a valid pointer to an array of @pDataSize@ bytes
--
-- -   #VUID-vkGetPipelineCacheData-pipelineCache-parent# @pipelineCache@
--     /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.INCOMPLETE'
--
-- [<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.Handles.Device', 'Vulkan.Core10.Handles.PipelineCache'
getPipelineCacheData :: forall io
                      . (MonadIO io)
                     => -- | @device@ is the logical device that owns the pipeline cache.
                        Device
                     -> -- | @pipelineCache@ is the pipeline cache to retrieve data from.
                        PipelineCache
                     -> io (Result, ("data" ::: ByteString))
getPipelineCacheData :: Device -> PipelineCache -> io (Result, "data" ::: ByteString)
getPipelineCacheData Device
device PipelineCache
pipelineCache = IO (Result, "data" ::: ByteString)
-> io (Result, "data" ::: ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, "data" ::: ByteString)
 -> io (Result, "data" ::: ByteString))
-> (ContT
      (Result, "data" ::: ByteString) IO (Result, "data" ::: ByteString)
    -> IO (Result, "data" ::: ByteString))
-> ContT
     (Result, "data" ::: ByteString) IO (Result, "data" ::: ByteString)
-> io (Result, "data" ::: ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
  (Result, "data" ::: ByteString) IO (Result, "data" ::: ByteString)
-> IO (Result, "data" ::: ByteString)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
   (Result, "data" ::: ByteString) IO (Result, "data" ::: ByteString)
 -> io (Result, "data" ::: ByteString))
-> ContT
     (Result, "data" ::: ByteString) IO (Result, "data" ::: ByteString)
-> io (Result, "data" ::: ByteString)
forall a b. (a -> b) -> a -> b
$ do
  let vkGetPipelineCacheDataPtr :: FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pDataSize" ::: Ptr CSize)
   -> ("pData" ::: Ptr ())
   -> IO Result)
vkGetPipelineCacheDataPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("pDataSize" ::: Ptr CSize)
      -> ("pData" ::: Ptr ())
      -> IO Result)
pVkGetPipelineCacheData (case Device
device of Device{DeviceCmds
deviceCmds :: DeviceCmds
$sel:deviceCmds:Device :: Device -> DeviceCmds
deviceCmds} -> DeviceCmds
deviceCmds)
  IO () -> ContT (Result, "data" ::: ByteString) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "data" ::: ByteString) IO ())
-> IO () -> ContT (Result, "data" ::: ByteString) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pDataSize" ::: Ptr CSize)
   -> ("pData" ::: Ptr ())
   -> IO Result)
vkGetPipelineCacheDataPtr FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pDataSize" ::: Ptr CSize)
   -> ("pData" ::: Ptr ())
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("pDataSize" ::: Ptr CSize)
      -> ("pData" ::: Ptr ())
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pDataSize" ::: Ptr CSize)
   -> ("pData" ::: Ptr ())
   -> 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 vkGetPipelineCacheData is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkGetPipelineCacheData' :: Ptr Device_T
-> PipelineCache
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result
vkGetPipelineCacheData' = FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pDataSize" ::: Ptr CSize)
   -> ("pData" ::: Ptr ())
   -> IO Result)
-> Ptr Device_T
-> PipelineCache
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result
mkVkGetPipelineCacheData FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("pDataSize" ::: Ptr CSize)
   -> ("pData" ::: Ptr ())
   -> IO Result)
vkGetPipelineCacheDataPtr
  let device' :: Ptr Device_T
device' = Device -> Ptr Device_T
deviceHandle (Device
device)
  "pDataSize" ::: Ptr CSize
pPDataSize <- ((("pDataSize" ::: Ptr CSize)
  -> IO (Result, "data" ::: ByteString))
 -> IO (Result, "data" ::: ByteString))
-> ContT
     (Result, "data" ::: ByteString) IO ("pDataSize" ::: Ptr CSize)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pDataSize" ::: Ptr CSize)
   -> IO (Result, "data" ::: ByteString))
  -> IO (Result, "data" ::: ByteString))
 -> ContT
      (Result, "data" ::: ByteString) IO ("pDataSize" ::: Ptr CSize))
-> ((("pDataSize" ::: Ptr CSize)
     -> IO (Result, "data" ::: ByteString))
    -> IO (Result, "data" ::: ByteString))
-> ContT
     (Result, "data" ::: ByteString) IO ("pDataSize" ::: Ptr CSize)
forall a b. (a -> b) -> a -> b
$ IO ("pDataSize" ::: Ptr CSize)
-> (("pDataSize" ::: Ptr CSize) -> IO ())
-> (("pDataSize" ::: Ptr CSize)
    -> IO (Result, "data" ::: ByteString))
-> IO (Result, "data" ::: ByteString)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pDataSize" ::: Ptr CSize)
forall a. Int -> IO (Ptr a)
callocBytes @CSize Int
8) ("pDataSize" ::: Ptr CSize) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r <- IO Result -> ContT (Result, "data" ::: ByteString) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Result, "data" ::: ByteString) IO Result)
-> IO Result -> ContT (Result, "data" ::: ByteString) IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPipelineCacheData" (Ptr Device_T
-> PipelineCache
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result
vkGetPipelineCacheData' Ptr Device_T
device' (PipelineCache
pipelineCache) ("pDataSize" ::: Ptr CSize
pPDataSize) ("pData" ::: Ptr ()
forall a. Ptr a
nullPtr))
  IO () -> ContT (Result, "data" ::: ByteString) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "data" ::: ByteString) IO ())
-> IO () -> ContT (Result, "data" ::: ByteString) 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))
  CSize
pDataSize <- IO CSize -> ContT (Result, "data" ::: ByteString) IO CSize
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO CSize -> ContT (Result, "data" ::: ByteString) IO CSize)
-> IO CSize -> ContT (Result, "data" ::: ByteString) IO CSize
forall a b. (a -> b) -> a -> b
$ ("pDataSize" ::: Ptr CSize) -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize "pDataSize" ::: Ptr CSize
pPDataSize
  "pData" ::: Ptr ()
pPData <- ((("pData" ::: Ptr ()) -> IO (Result, "data" ::: ByteString))
 -> IO (Result, "data" ::: ByteString))
-> ContT (Result, "data" ::: ByteString) IO ("pData" ::: Ptr ())
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pData" ::: Ptr ()) -> IO (Result, "data" ::: ByteString))
  -> IO (Result, "data" ::: ByteString))
 -> ContT (Result, "data" ::: ByteString) IO ("pData" ::: Ptr ()))
-> ((("pData" ::: Ptr ()) -> IO (Result, "data" ::: ByteString))
    -> IO (Result, "data" ::: ByteString))
-> ContT (Result, "data" ::: ByteString) IO ("pData" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ IO ("pData" ::: Ptr ())
-> (("pData" ::: Ptr ()) -> IO ())
-> (("pData" ::: Ptr ()) -> IO (Result, "data" ::: ByteString))
-> IO (Result, "data" ::: ByteString)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pData" ::: Ptr ())
forall a. Int -> IO (Ptr a)
callocBytes @(()) (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((CSize -> Word64
coerce @CSize @Word64 CSize
pDataSize)))) ("pData" ::: Ptr ()) -> IO ()
forall a. Ptr a -> IO ()
free
  Result
r' <- IO Result -> ContT (Result, "data" ::: ByteString) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Result, "data" ::: ByteString) IO Result)
-> IO Result -> ContT (Result, "data" ::: ByteString) IO Result
forall a b. (a -> b) -> a -> b
$ String -> IO Result -> IO Result
forall a. String -> IO a -> IO a
traceAroundEvent String
"vkGetPipelineCacheData" (Ptr Device_T
-> PipelineCache
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result
vkGetPipelineCacheData' Ptr Device_T
device' (PipelineCache
pipelineCache) ("pDataSize" ::: Ptr CSize
pPDataSize) ("pData" ::: Ptr ()
pPData))
  IO () -> ContT (Result, "data" ::: ByteString) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Result, "data" ::: ByteString) IO ())
-> IO () -> ContT (Result, "data" ::: ByteString) 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'))
  CSize
pDataSize'' <- IO CSize -> ContT (Result, "data" ::: ByteString) IO CSize
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO CSize -> ContT (Result, "data" ::: ByteString) IO CSize)
-> IO CSize -> ContT (Result, "data" ::: ByteString) IO CSize
forall a b. (a -> b) -> a -> b
$ ("pDataSize" ::: Ptr CSize) -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize "pDataSize" ::: Ptr CSize
pPDataSize
  "data" ::: ByteString
pData' <- IO ("data" ::: ByteString)
-> ContT (Result, "data" ::: ByteString) IO ("data" ::: ByteString)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("data" ::: ByteString)
 -> ContT
      (Result, "data" ::: ByteString) IO ("data" ::: ByteString))
-> IO ("data" ::: ByteString)
-> ContT (Result, "data" ::: ByteString) IO ("data" ::: ByteString)
forall a b. (a -> b) -> a -> b
$ CStringLen -> IO ("data" ::: ByteString)
packCStringLen  (("pData" ::: Ptr ()) -> Ptr CChar
forall a b. Ptr a -> Ptr b
castPtr @() @CChar "pData" ::: Ptr ()
pPData, (Word64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((CSize -> Word64
coerce @CSize @Word64 CSize
pDataSize''))))
  (Result, "data" ::: ByteString)
-> ContT
     (Result, "data" ::: ByteString) IO (Result, "data" ::: ByteString)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, "data" ::: ByteString)
 -> ContT
      (Result, "data" ::: ByteString) IO (Result, "data" ::: ByteString))
-> (Result, "data" ::: ByteString)
-> ContT
     (Result, "data" ::: ByteString) IO (Result, "data" ::: ByteString)
forall a b. (a -> b) -> a -> b
$ ((Result
r'), "data" ::: ByteString
pData')


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

-- | vkMergePipelineCaches - Combine the data stores of pipeline caches
--
-- = Description
--
-- Note
--
-- The details of the merge operation are implementation-dependent, but
-- implementations /should/ merge the contents of the specified pipelines
-- and prune duplicate entries.
--
-- == Valid Usage
--
-- -   #VUID-vkMergePipelineCaches-dstCache-00770# @dstCache@ /must/ not
--     appear in the list of source caches
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-vkMergePipelineCaches-device-parameter# @device@ /must/ be a
--     valid 'Vulkan.Core10.Handles.Device' handle
--
-- -   #VUID-vkMergePipelineCaches-dstCache-parameter# @dstCache@ /must/ be
--     a valid 'Vulkan.Core10.Handles.PipelineCache' handle
--
-- -   #VUID-vkMergePipelineCaches-pSrcCaches-parameter# @pSrcCaches@
--     /must/ be a valid pointer to an array of @srcCacheCount@ valid
--     'Vulkan.Core10.Handles.PipelineCache' handles
--
-- -   #VUID-vkMergePipelineCaches-srcCacheCount-arraylength#
--     @srcCacheCount@ /must/ be greater than @0@
--
-- -   #VUID-vkMergePipelineCaches-dstCache-parent# @dstCache@ /must/ have
--     been created, allocated, or retrieved from @device@
--
-- -   #VUID-vkMergePipelineCaches-pSrcCaches-parent# Each element of
--     @pSrcCaches@ /must/ have been created, allocated, or retrieved from
--     @device@
--
-- == Host Synchronization
--
-- -   Host access to @dstCache@ /must/ be externally synchronized
--
-- == Return Codes
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-successcodes Success>]
--
--     -   'Vulkan.Core10.Enums.Result.SUCCESS'
--
-- [<https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#fundamentals-errorcodes Failure>]
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_HOST_MEMORY'
--
--     -   'Vulkan.Core10.Enums.Result.ERROR_OUT_OF_DEVICE_MEMORY'
--
-- = 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.PipelineCache'
mergePipelineCaches :: forall io
                     . (MonadIO io)
                    => -- | @device@ is the logical device that owns the pipeline cache objects.
                       Device
                    -> -- | @dstCache@ is the handle of the pipeline cache to merge results into.
                       ("dstCache" ::: PipelineCache)
                    -> -- | @pSrcCaches@ is a pointer to an array of pipeline cache handles, which
                       -- will be merged into @dstCache@. The previous contents of @dstCache@ are
                       -- included after the merge.
                       ("srcCaches" ::: Vector PipelineCache)
                    -> io ()
mergePipelineCaches :: Device
-> PipelineCache -> ("srcCaches" ::: Vector PipelineCache) -> io ()
mergePipelineCaches Device
device PipelineCache
dstCache "srcCaches" ::: Vector PipelineCache
srcCaches = 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 vkMergePipelineCachesPtr :: FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("srcCacheCount" ::: Word32)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
vkMergePipelineCachesPtr = DeviceCmds
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("srcCacheCount" ::: Word32)
      -> ("pPipelineCache" ::: Ptr PipelineCache)
      -> IO Result)
pVkMergePipelineCaches (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
   -> PipelineCache
   -> ("srcCacheCount" ::: Word32)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
vkMergePipelineCachesPtr FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("srcCacheCount" ::: Word32)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
-> FunPtr
     (Ptr Device_T
      -> PipelineCache
      -> ("srcCacheCount" ::: Word32)
      -> ("pPipelineCache" ::: Ptr PipelineCache)
      -> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("srcCacheCount" ::: Word32)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> 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 vkMergePipelineCaches is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
  let vkMergePipelineCaches' :: Ptr Device_T
-> PipelineCache
-> ("srcCacheCount" ::: Word32)
-> ("pPipelineCache" ::: Ptr PipelineCache)
-> IO Result
vkMergePipelineCaches' = FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("srcCacheCount" ::: Word32)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
-> Ptr Device_T
-> PipelineCache
-> ("srcCacheCount" ::: Word32)
-> ("pPipelineCache" ::: Ptr PipelineCache)
-> IO Result
mkVkMergePipelineCaches FunPtr
  (Ptr Device_T
   -> PipelineCache
   -> ("srcCacheCount" ::: Word32)
   -> ("pPipelineCache" ::: Ptr PipelineCache)
   -> IO Result)
vkMergePipelineCachesPtr
  "pPipelineCache" ::: Ptr PipelineCache
pPSrcCaches <- ((("pPipelineCache" ::: Ptr PipelineCache) -> IO ()) -> IO ())
-> ContT () IO ("pPipelineCache" ::: Ptr PipelineCache)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pPipelineCache" ::: Ptr PipelineCache) -> IO ()) -> IO ())
 -> ContT () IO ("pPipelineCache" ::: Ptr PipelineCache))
-> ((("pPipelineCache" ::: Ptr PipelineCache) -> IO ()) -> IO ())
-> ContT () IO ("pPipelineCache" ::: Ptr PipelineCache)
forall a b. (a -> b) -> a -> b
$ Int -> (("pPipelineCache" ::: Ptr PipelineCache) -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @PipelineCache ((("srcCaches" ::: Vector PipelineCache) -> Int
forall a. Vector a -> Int
Data.Vector.length ("srcCaches" ::: Vector PipelineCache
srcCaches)) 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 -> PipelineCache -> IO ())
-> ("srcCaches" ::: Vector PipelineCache) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i PipelineCache
e -> ("pPipelineCache" ::: Ptr PipelineCache) -> PipelineCache -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPipelineCache" ::: Ptr PipelineCache
pPSrcCaches ("pPipelineCache" ::: Ptr PipelineCache)
-> Int -> "pPipelineCache" ::: Ptr PipelineCache
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineCache) (PipelineCache
e)) ("srcCaches" ::: Vector PipelineCache
srcCaches)
  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
"vkMergePipelineCaches" (Ptr Device_T
-> PipelineCache
-> ("srcCacheCount" ::: Word32)
-> ("pPipelineCache" ::: Ptr PipelineCache)
-> IO Result
vkMergePipelineCaches' (Device -> Ptr Device_T
deviceHandle (Device
device)) (PipelineCache
dstCache) ((Int -> "srcCacheCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("srcCaches" ::: Vector PipelineCache) -> Int
forall a. Vector a -> Int
Data.Vector.length (("srcCaches" ::: Vector PipelineCache) -> Int)
-> ("srcCaches" ::: Vector PipelineCache) -> Int
forall a b. (a -> b) -> a -> b
$ ("srcCaches" ::: Vector PipelineCache
srcCaches)) :: Word32)) ("pPipelineCache" ::: Ptr PipelineCache
pPSrcCaches))
  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))


-- | VkPipelineCacheCreateInfo - Structure specifying parameters of a newly
-- created pipeline cache
--
-- == Valid Usage
--
-- -   #VUID-VkPipelineCacheCreateInfo-initialDataSize-00768# If
--     @initialDataSize@ is not @0@, it /must/ be equal to the size of
--     @pInitialData@, as returned by 'getPipelineCacheData' when
--     @pInitialData@ was originally retrieved
--
-- -   #VUID-VkPipelineCacheCreateInfo-initialDataSize-00769# If
--     @initialDataSize@ is not @0@, @pInitialData@ /must/ have been
--     retrieved from a previous call to 'getPipelineCacheData'
--
-- -   #VUID-VkPipelineCacheCreateInfo-pipelineCreationCacheControl-02892#
--     If the
--     <https://www.khronos.org/registry/vulkan/specs/1.2-extensions/html/vkspec.html#features-pipelineCreationCacheControl pipelineCreationCacheControl>
--     feature is not enabled, @flags@ /must/ not include
--     'Vulkan.Core10.Enums.PipelineCacheCreateFlagBits.PIPELINE_CACHE_CREATE_EXTERNALLY_SYNCHRONIZED_BIT_EXT'
--
-- == Valid Usage (Implicit)
--
-- -   #VUID-VkPipelineCacheCreateInfo-sType-sType# @sType@ /must/ be
--     'Vulkan.Core10.Enums.StructureType.STRUCTURE_TYPE_PIPELINE_CACHE_CREATE_INFO'
--
-- -   #VUID-VkPipelineCacheCreateInfo-pNext-pNext# @pNext@ /must/ be
--     @NULL@
--
-- -   #VUID-VkPipelineCacheCreateInfo-flags-parameter# @flags@ /must/ be a
--     valid combination of
--     'Vulkan.Core10.Enums.PipelineCacheCreateFlagBits.PipelineCacheCreateFlagBits'
--     values
--
-- -   #VUID-VkPipelineCacheCreateInfo-pInitialData-parameter# If
--     @initialDataSize@ is not @0@, @pInitialData@ /must/ be a valid
--     pointer to an array of @initialDataSize@ bytes
--
-- = 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.PipelineCacheCreateFlagBits.PipelineCacheCreateFlags',
-- 'Vulkan.Core10.Enums.StructureType.StructureType', 'createPipelineCache'
data PipelineCacheCreateInfo = PipelineCacheCreateInfo
  { -- | @flags@ is a bitmask of
    -- 'Vulkan.Core10.Enums.PipelineCacheCreateFlagBits.PipelineCacheCreateFlagBits'
    -- specifying the behavior of the pipeline cache.
    PipelineCacheCreateInfo -> PipelineCacheCreateFlags
flags :: PipelineCacheCreateFlags
  , -- | @initialDataSize@ is the number of bytes in @pInitialData@. If
    -- @initialDataSize@ is zero, the pipeline cache will initially be empty.
    PipelineCacheCreateInfo -> Word64
initialDataSize :: Word64
  , -- | @pInitialData@ is a pointer to previously retrieved pipeline cache data.
    -- If the pipeline cache data is incompatible (as defined below) with the
    -- device, the pipeline cache will be initially empty. If @initialDataSize@
    -- is zero, @pInitialData@ is ignored.
    PipelineCacheCreateInfo -> "pData" ::: Ptr ()
initialData :: Ptr ()
  }
  deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PipelineCacheCreateInfo)
#endif
deriving instance Show PipelineCacheCreateInfo

instance ToCStruct PipelineCacheCreateInfo where
  withCStruct :: PipelineCacheCreateInfo
-> (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b)
-> IO b
withCStruct PipelineCacheCreateInfo
x ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b
f = Int
-> (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b)
-> IO b
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 ((("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b) -> IO b)
-> (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \"pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p -> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> PipelineCacheCreateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p PipelineCacheCreateInfo
x (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b
f "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p)
  pokeCStruct :: ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> PipelineCacheCreateInfo -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p PipelineCacheCreateInfo{Word64
"pData" ::: Ptr ()
PipelineCacheCreateFlags
initialData :: "pData" ::: Ptr ()
initialDataSize :: Word64
flags :: PipelineCacheCreateFlags
$sel:initialData:PipelineCacheCreateInfo :: PipelineCacheCreateInfo -> "pData" ::: Ptr ()
$sel:initialDataSize:PipelineCacheCreateInfo :: PipelineCacheCreateInfo -> Word64
$sel:flags:PipelineCacheCreateInfo :: PipelineCacheCreateInfo -> PipelineCacheCreateFlags
..} IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_CACHE_CREATE_INFO)
    Ptr ("pData" ::: Ptr ()) -> ("pData" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> Ptr ("pData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("pData" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr PipelineCacheCreateFlags -> PipelineCacheCreateFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> Ptr PipelineCacheCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineCacheCreateFlags)) (PipelineCacheCreateFlags
flags)
    ("pDataSize" ::: Ptr CSize) -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> "pDataSize" ::: Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
initialDataSize))
    Ptr ("pData" ::: Ptr ()) -> ("pData" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> Ptr ("pData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ()))) ("pData" ::: Ptr ()
initialData)
    IO b
f
  cStructSize :: Int
cStructSize = Int
40
  cStructAlignment :: Int
cStructAlignment = Int
8
  pokeZeroCStruct :: ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b -> IO b
pokeZeroCStruct "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p IO b
f = do
    Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_CACHE_CREATE_INFO)
    Ptr ("pData" ::: Ptr ()) -> ("pData" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> Ptr ("pData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) ("pData" ::: Ptr ()
forall a. Ptr a
nullPtr)
    Ptr ("pData" ::: Ptr ()) -> ("pData" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> Ptr ("pData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ()))) ("pData" ::: Ptr ()
forall a. Zero a => a
zero)
    IO b
f

instance FromCStruct PipelineCacheCreateInfo where
  peekCStruct :: ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> IO PipelineCacheCreateInfo
peekCStruct "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p = do
    PipelineCacheCreateFlags
flags <- Ptr PipelineCacheCreateFlags -> IO PipelineCacheCreateFlags
forall a. Storable a => Ptr a -> IO a
peek @PipelineCacheCreateFlags (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> Ptr PipelineCacheCreateFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineCacheCreateFlags))
    CSize
initialDataSize <- ("pDataSize" ::: Ptr CSize) -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> "pDataSize" ::: Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CSize))
    "pData" ::: Ptr ()
pInitialData <- Ptr ("pData" ::: Ptr ()) -> IO ("pData" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> Int -> Ptr ("pData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ())))
    PipelineCacheCreateInfo -> IO PipelineCacheCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PipelineCacheCreateInfo -> IO PipelineCacheCreateInfo)
-> PipelineCacheCreateInfo -> IO PipelineCacheCreateInfo
forall a b. (a -> b) -> a -> b
$ PipelineCacheCreateFlags
-> Word64 -> ("pData" ::: Ptr ()) -> PipelineCacheCreateInfo
PipelineCacheCreateInfo
             PipelineCacheCreateFlags
flags (CSize -> Word64
coerce @CSize @Word64 CSize
initialDataSize) "pData" ::: Ptr ()
pInitialData

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

instance Zero PipelineCacheCreateInfo where
  zero :: PipelineCacheCreateInfo
zero = PipelineCacheCreateFlags
-> Word64 -> ("pData" ::: Ptr ()) -> PipelineCacheCreateInfo
PipelineCacheCreateInfo
           PipelineCacheCreateFlags
forall a. Zero a => a
zero
           Word64
forall a. Zero a => a
zero
           "pData" ::: Ptr ()
forall a. Zero a => a
zero