{-# language CPP #-}
module Vulkan.Core10.PipelineCache ( createPipelineCache
, withPipelineCache
, destroyPipelineCache
, getPipelineCacheData
, mergePipelineCaches
, PipelineCacheCreateInfo(..)
) where
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Foreign.Marshal.Alloc (allocaBytesAligned)
import Foreign.Marshal.Alloc (callocBytes)
import Foreign.Marshal.Alloc (free)
import GHC.Base (when)
import GHC.IO (throwIO)
import GHC.Ptr (castPtr)
import GHC.Ptr (nullFunPtr)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import Data.ByteString (packCStringLen)
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 Control.Monad.IO.Class (MonadIO)
import Data.Typeable (Typeable)
import Foreign.C.Types (CChar)
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.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.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.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
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.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.Exception (VulkanException(..))
import Vulkan.Zero (Zero(..))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_PIPELINE_CACHE_CREATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
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 :: Device
-> PipelineCacheCreateInfo
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io PipelineCache
createPipelineCache device :: Device
device createInfo :: PipelineCacheCreateInfo
createInfo allocator :: "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 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
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 "" "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
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 j :: 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 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
$ 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)
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
device pCreateInfo :: PipelineCacheCreateInfo
pCreateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: 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 ()
destroyPipelineCache :: forall io . MonadIO io => Device -> PipelineCache -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
destroyPipelineCache :: Device
-> PipelineCache
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
destroyPipelineCache device :: Device
device pipelineCache :: PipelineCache
pipelineCache allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ())
-> (ContT () IO () -> IO ()) -> ContT () IO () -> io ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT () IO () -> IO ()
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT () IO () -> io ()) -> ContT () IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkDestroyPipelineCachePtr :: FunPtr
(Ptr Device_T
-> PipelineCache
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkDestroyPipelineCachePtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> PipelineCache
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
pVkDestroyPipelineCache (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> 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 "" "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
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "pAllocator" ::: Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
Just j :: AllocationCallbacks
j -> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ())
-> ContT () IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()) -> IO ()
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> 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
getPipelineCacheData :: forall io . MonadIO io => Device -> PipelineCache -> io (Result, ("data" ::: ByteString))
getPipelineCacheData :: Device -> PipelineCache -> io (Result, "data" ::: ByteString)
getPipelineCacheData device :: Device
device pipelineCache :: 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 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
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 "" "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 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
$ 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 a :: Word64
a) -> Word64
a) 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
$ 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 a :: Word64
a) -> Word64
a) 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
mergePipelineCaches :: forall io . MonadIO io => Device -> ("dstCache" ::: PipelineCache) -> ("srcCaches" ::: Vector PipelineCache) -> io ()
mergePipelineCaches :: Device
-> PipelineCache -> ("srcCaches" ::: Vector PipelineCache) -> io ()
mergePipelineCaches device :: Device
device dstCache :: PipelineCache
dstCache srcCaches :: "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 (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> 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 "" "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
-> Int
-> (("pPipelineCache" ::: Ptr PipelineCache) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @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
* 8) 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_ (\i :: Int
i e :: 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` (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
$ 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))
data PipelineCacheCreateInfo = PipelineCacheCreateInfo
{
PipelineCacheCreateInfo -> PipelineCacheCreateFlags
flags :: PipelineCacheCreateFlags
,
PipelineCacheCreateInfo -> Word64
initialDataSize :: Word64
,
PipelineCacheCreateInfo -> "pData" ::: Ptr ()
initialData :: Ptr ()
}
deriving (Typeable)
deriving instance Show PipelineCacheCreateInfo
instance ToCStruct PipelineCacheCreateInfo where
withCStruct :: PipelineCacheCreateInfo
-> (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b)
-> IO b
withCStruct x :: PipelineCacheCreateInfo
x f :: ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b
f = Int
-> Int
-> (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b) -> IO b)
-> (("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b)
-> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "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 p :: "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p PipelineCacheCreateInfo{..} f :: 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` 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` 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` 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` 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` 32 :: Ptr (Ptr ()))) ("pData" ::: Ptr ()
initialData)
IO b
f
cStructSize :: Int
cStructSize = 40
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pCreateInfo" ::: Ptr PipelineCacheCreateInfo) -> IO b -> IO b
pokeZeroCStruct p :: "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
p f :: 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` 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` 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` 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 p :: "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` 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` 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` 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 a :: Word64
a) -> Word64
a) CSize
initialDataSize) "pData" ::: Ptr ()
pInitialData
instance Storable PipelineCacheCreateInfo where
sizeOf :: PipelineCacheCreateInfo -> Int
sizeOf ~PipelineCacheCreateInfo
_ = 40
alignment :: PipelineCacheCreateInfo -> Int
alignment ~PipelineCacheCreateInfo
_ = 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 ptr :: "pCreateInfo" ::: Ptr PipelineCacheCreateInfo
ptr poked :: 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