{-# language CPP #-}
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
createPipelineCache :: forall io
. (MonadIO io)
=>
Device
->
PipelineCacheCreateInfo
->
("allocator" ::: Maybe AllocationCallbacks)
-> io (PipelineCache)
createPipelineCache :: forall (io :: * -> *).
MonadIO io =>
Device
-> PipelineCacheCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PipelineCache
createPipelineCache Device
device PipelineCacheCreateInfo
createInfo "allocator" ::: Maybe AllocationCallbacks
allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT 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)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pPipelineCache" ::: Ptr PipelineCache)
-> IO Result)
vkCreatePipelineCachePtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkCreatePipelineCache is null" forall a. Maybe a
Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ 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 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just AllocationCallbacks
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
"pPipelineCache" ::: Ptr PipelineCache
pPPipelineCache <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @PipelineCache Int
8) forall a. Ptr a -> IO ()
free
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ 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))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
PipelineCache
pPipelineCache <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @PipelineCache "pPipelineCache" ::: Ptr PipelineCache
pPPipelineCache
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ (PipelineCache
pPipelineCache)
withPipelineCache :: forall io r . MonadIO io => Device -> PipelineCacheCreateInfo -> Maybe AllocationCallbacks -> (io PipelineCache -> (PipelineCache -> io ()) -> r) -> r
withPipelineCache :: forall (io :: * -> *) r.
MonadIO io =>
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 (forall (io :: * -> *).
MonadIO io =>
Device
-> PipelineCacheCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PipelineCache
createPipelineCache Device
device PipelineCacheCreateInfo
pCreateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
(\(PipelineCache
o0) -> 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 ()
destroyPipelineCache :: forall io
. (MonadIO io)
=>
Device
->
PipelineCache
->
("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyPipelineCache :: forall (io :: * -> *).
MonadIO io =>
Device
-> PipelineCache
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyPipelineCache Device
device PipelineCache
pipelineCache "allocator" ::: Maybe AllocationCallbacks
allocator = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT 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)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> PipelineCache
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyPipelineCachePtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkDestroyPipelineCache is null" forall a. Maybe a
Nothing 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 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Ptr a
nullPtr
Just AllocationCallbacks
j -> forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ 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)
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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
getPipelineCacheData :: forall io
. (MonadIO io)
=>
Device
->
PipelineCache
-> io (Result, ("data" ::: ByteString))
getPipelineCacheData :: forall (io :: * -> *).
MonadIO io =>
Device -> PipelineCache -> io (Result, "data" ::: ByteString)
getPipelineCacheData Device
device PipelineCache
pipelineCache = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT 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)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> PipelineCache
-> ("pDataSize" ::: Ptr CSize)
-> ("pData" ::: Ptr ())
-> IO Result)
vkGetPipelineCacheDataPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkGetPipelineCacheData is null" forall a. Maybe a
Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @CSize Int
8) forall a. Ptr a -> IO ()
free
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ 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)
(forall a. Ptr a
nullPtr))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
CSize
pDataSize <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @CSize "pDataSize" ::: Ptr CSize
pPDataSize
"pData" ::: Ptr ()
pPData <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (forall a. Int -> IO (Ptr a)
callocBytes @(()) (forall a b. (Integral a, Num b) => a -> b
fromIntegral ((coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 CSize
pDataSize)))) forall a. Ptr a -> IO ()
free
Result
r' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ 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))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r' forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r'))
CSize
pDataSize'' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall a. Storable a => Ptr a -> IO a
peek @CSize "pDataSize" ::: Ptr CSize
pPDataSize
"data" ::: ByteString
pData' <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ CStringLen -> IO ("data" ::: ByteString)
packCStringLen ( forall a b. Ptr a -> Ptr b
castPtr @() @CChar "pData" ::: Ptr ()
pPData
, (forall a b. (Integral a, Num b) => a -> b
fromIntegral ((coerce :: forall a b. Coercible a b => a -> b
coerce @CSize @Word64 CSize
pDataSize''))) )
forall (f :: * -> *) a. Applicative f => a -> f a
pure 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
mergePipelineCaches :: forall io
. (MonadIO io)
=>
Device
->
("dstCache" ::: PipelineCache)
->
("srcCaches" ::: Vector PipelineCache)
-> io ()
mergePipelineCaches :: forall (io :: * -> *).
MonadIO io =>
Device
-> PipelineCache -> ("srcCaches" ::: Vector PipelineCache) -> io ()
mergePipelineCaches Device
device PipelineCache
dstCache "srcCaches" ::: Vector PipelineCache
srcCaches = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT 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)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> PipelineCache
-> ("srcCacheCount" ::: Word32)
-> ("pPipelineCache" ::: Ptr PipelineCache)
-> IO Result)
vkMergePipelineCachesPtr forall a. Eq a => a -> a -> Bool
/= forall a. FunPtr a
nullFunPtr) forall a b. (a -> b) -> a -> b
$
forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ Maybe Handle
-> IOErrorType
-> String
-> String
-> Maybe CInt
-> Maybe String
-> IOException
IOError forall a. Maybe a
Nothing IOErrorType
InvalidArgument String
"" String
"The function pointer for vkMergePipelineCaches is null" forall a. Maybe a
Nothing 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 <- forall {k} (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT forall a b. (a -> b) -> a -> b
$ forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes @PipelineCache ((forall a. Vector a -> Int
Data.Vector.length ("srcCaches" ::: Vector PipelineCache
srcCaches)) forall a. Num a => a -> a -> a
* Int
8)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\Int
i PipelineCache
e -> forall a. Storable a => Ptr a -> a -> IO ()
poke ("pPipelineCache" ::: Ptr PipelineCache
pPSrcCaches forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
8 forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr PipelineCache) (PipelineCache
e)) ("srcCaches" ::: Vector PipelineCache
srcCaches)
Result
r <- forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ 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)
((forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Vector a -> Int
Data.Vector.length forall a b. (a -> b) -> a -> b
$ ("srcCaches" ::: Vector PipelineCache
srcCaches)) :: Word32))
("pPipelineCache" ::: Ptr PipelineCache
pPSrcCaches))
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
data PipelineCacheCreateInfo = PipelineCacheCreateInfo
{
PipelineCacheCreateInfo -> PipelineCacheCreateFlags
flags :: PipelineCacheCreateFlags
,
PipelineCacheCreateInfo -> Word64
initialDataSize :: Word64
,
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 :: forall b.
PipelineCacheCreateInfo
-> (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b)
-> IO b
withCStruct PipelineCacheCreateInfo
x ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b
f = forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
40 forall a b. (a -> b) -> a -> b
$ \"pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p -> 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 :: forall b.
("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
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_CACHE_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineCacheCreateFlags)) (PipelineCacheCreateFlags
flags)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CSize)) (Word64 -> CSize
CSize (Word64
initialDataSize))
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p 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 :: forall b.
("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b -> IO b
pokeZeroCStruct "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p IO b
f = do
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_PIPELINE_CACHE_CREATE_INFO)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8 :: Ptr (Ptr ()))) (forall a. Ptr a
nullPtr)
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (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 <- forall a. Storable a => Ptr a -> IO a
peek @PipelineCacheCreateFlags (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16 :: Ptr PipelineCacheCreateFlags))
CSize
initialDataSize <- forall a. Storable a => Ptr a -> IO a
peek @CSize (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24 :: Ptr CSize))
"pData" ::: Ptr ()
pInitialData <- forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32 :: Ptr (Ptr ())))
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ PipelineCacheCreateFlags
-> Word64 -> ("pData" ::: Ptr ()) -> PipelineCacheCreateInfo
PipelineCacheCreateInfo
PipelineCacheCreateFlags
flags (coerce :: forall a b. Coercible a b => a -> b
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 = forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo)
-> PipelineCacheCreateInfo -> IO ()
poke "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
ptr PipelineCacheCreateInfo
poked = forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
ptr PipelineCacheCreateInfo
poked (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PipelineCacheCreateInfo where
zero :: PipelineCacheCreateInfo
zero = PipelineCacheCreateFlags
-> Word64 -> ("pData" ::: Ptr ()) -> PipelineCacheCreateInfo
PipelineCacheCreateInfo
forall a. Zero a => a
zero
forall a. Zero a => a
zero
forall a. Zero a => a
zero