{-# language CPP #-}
module Vulkan.Core10.Memory ( allocateMemory
, withMemory
, freeMemory
, mapMemory
, withMappedMemory
, unmapMemory
, flushMappedMemoryRanges
, invalidateMappedMemoryRanges
, getDeviceMemoryCommitment
, MemoryAllocateInfo(..)
, MappedMemoryRange(..)
) where
import Control.Exception.Base (bracket)
import Control.Monad (unless)
import Control.Monad.IO.Class (liftIO)
import Data.Typeable (eqT)
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 Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import Control.Monad.IO.Class (MonadIO)
import Data.Type.Equality ((:~:)(Refl))
import Data.Typeable (Typeable)
import Foreign.Storable (Storable)
import Foreign.Storable (Storable(peek))
import Foreign.Storable (Storable(poke))
import qualified Foreign.Storable (Storable(..))
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import Data.Word (Word32)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
import Vulkan.NamedType ((:::))
import Vulkan.Core10.AllocationCallbacks (AllocationCallbacks)
import Vulkan.CStruct.Extends (Chain)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_dedicated_allocation (DedicatedAllocationMemoryAllocateInfoNV)
import Vulkan.Core10.Handles (Device)
import Vulkan.Core10.Handles (Device(..))
import Vulkan.Dynamic (DeviceCmds(pVkAllocateMemory))
import Vulkan.Dynamic (DeviceCmds(pVkFlushMappedMemoryRanges))
import Vulkan.Dynamic (DeviceCmds(pVkFreeMemory))
import Vulkan.Dynamic (DeviceCmds(pVkGetDeviceMemoryCommitment))
import Vulkan.Dynamic (DeviceCmds(pVkInvalidateMappedMemoryRanges))
import Vulkan.Dynamic (DeviceCmds(pVkMapMemory))
import Vulkan.Dynamic (DeviceCmds(pVkUnmapMemory))
import Vulkan.Core10.Handles (DeviceMemory)
import Vulkan.Core10.Handles (DeviceMemory(..))
import Vulkan.Core10.BaseType (DeviceSize)
import Vulkan.Core10.Handles (Device_T)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_external_memory (ExportMemoryAllocateInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_external_memory (ExportMemoryAllocateInfoNV)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_external_memory_win32 (ExportMemoryWin32HandleInfoKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_external_memory_win32 (ExportMemoryWin32HandleInfoNV)
import Vulkan.CStruct.Extends (Extends)
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (Extensible(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import {-# SOURCE #-} Vulkan.Extensions.VK_ANDROID_external_memory_android_hardware_buffer (ImportAndroidHardwareBufferInfoANDROID)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_external_memory_fd (ImportMemoryFdInfoKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_external_memory_host (ImportMemoryHostPointerInfoEXT)
import {-# SOURCE #-} Vulkan.Extensions.VK_KHR_external_memory_win32 (ImportMemoryWin32HandleInfoKHR)
import {-# SOURCE #-} Vulkan.Extensions.VK_NV_external_memory_win32 (ImportMemoryWin32HandleInfoNV)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_device_group (MemoryAllocateFlagsInfo)
import {-# SOURCE #-} Vulkan.Core11.Promoted_From_VK_KHR_dedicated_allocation (MemoryDedicatedAllocateInfo)
import Vulkan.Core10.Enums.MemoryMapFlags (MemoryMapFlags)
import Vulkan.Core10.Enums.MemoryMapFlags (MemoryMapFlags(..))
import {-# SOURCE #-} Vulkan.Core12.Promoted_From_VK_KHR_buffer_device_address (MemoryOpaqueCaptureAddressAllocateInfo)
import {-# SOURCE #-} Vulkan.Extensions.VK_EXT_memory_priority (MemoryPriorityAllocateInfoEXT)
import Vulkan.CStruct.Extends (PeekChain)
import Vulkan.CStruct.Extends (PeekChain(..))
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (PokeChain(..))
import Vulkan.Core10.Enums.Result (Result)
import Vulkan.Core10.Enums.Result (Result(..))
import Vulkan.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_MAPPED_MEMORY_RANGE))
import Vulkan.Core10.Enums.StructureType (StructureType(STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO))
import Vulkan.Core10.Enums.Result (Result(SUCCESS))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkAllocateMemory
:: FunPtr (Ptr Device_T -> Ptr (MemoryAllocateInfo a) -> Ptr AllocationCallbacks -> Ptr DeviceMemory -> IO Result) -> Ptr Device_T -> Ptr (MemoryAllocateInfo a) -> Ptr AllocationCallbacks -> Ptr DeviceMemory -> IO Result
allocateMemory :: forall a io . (Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) => Device -> MemoryAllocateInfo a -> ("allocator" ::: Maybe AllocationCallbacks) -> io (DeviceMemory)
allocateMemory :: Device
-> MemoryAllocateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io DeviceMemory
allocateMemory device :: Device
device allocateInfo :: MemoryAllocateInfo a
allocateInfo allocator :: "allocator" ::: Maybe AllocationCallbacks
allocator = IO DeviceMemory -> io DeviceMemory
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DeviceMemory -> io DeviceMemory)
-> (ContT DeviceMemory IO DeviceMemory -> IO DeviceMemory)
-> ContT DeviceMemory IO DeviceMemory
-> io DeviceMemory
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT DeviceMemory IO DeviceMemory -> IO DeviceMemory
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT DeviceMemory IO DeviceMemory -> io DeviceMemory)
-> ContT DeviceMemory IO DeviceMemory -> io DeviceMemory
forall a b. (a -> b) -> a -> b
$ do
let vkAllocateMemoryPtr :: FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result)
vkAllocateMemoryPtr = DeviceCmds
-> forall (a :: [*]).
FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result)
pVkAllocateMemory (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT DeviceMemory IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DeviceMemory IO ())
-> IO () -> ContT DeviceMemory IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result)
vkAllocateMemoryPtr FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> 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 vkAllocateMemory is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkAllocateMemory' :: Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result
vkAllocateMemory' = FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result)
-> Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result
forall (a :: [*]).
FunPtr
(Ptr Device_T
-> Ptr (MemoryAllocateInfo a)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result)
-> Ptr Device_T
-> Ptr (MemoryAllocateInfo a)
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result
mkVkAllocateMemory FunPtr
(Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result)
vkAllocateMemoryPtr
"pAllocateInfo" ::: Ptr (MemoryAllocateInfo a)
pAllocateInfo <- ((("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> IO DeviceMemory)
-> IO DeviceMemory)
-> ContT
DeviceMemory IO ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> IO DeviceMemory)
-> IO DeviceMemory)
-> ContT
DeviceMemory IO ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a)))
-> ((("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> IO DeviceMemory)
-> IO DeviceMemory)
-> ContT
DeviceMemory IO ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
forall a b. (a -> b) -> a -> b
$ MemoryAllocateInfo a
-> (("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> IO DeviceMemory)
-> IO DeviceMemory
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (MemoryAllocateInfo a
allocateInfo)
"pAllocator" ::: Ptr AllocationCallbacks
pAllocator <- case ("allocator" ::: Maybe AllocationCallbacks
allocator) of
Nothing -> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ContT DeviceMemory 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 DeviceMemory)
-> IO DeviceMemory)
-> ContT DeviceMemory 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 DeviceMemory)
-> IO DeviceMemory)
-> ContT
DeviceMemory IO ("pAllocator" ::: Ptr AllocationCallbacks))
-> ((("pAllocator" ::: Ptr AllocationCallbacks) -> IO DeviceMemory)
-> IO DeviceMemory)
-> ContT DeviceMemory IO ("pAllocator" ::: Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks
-> (("pAllocator" ::: Ptr AllocationCallbacks) -> IO DeviceMemory)
-> IO DeviceMemory
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
"pMemory" ::: Ptr DeviceMemory
pPMemory <- ((("pMemory" ::: Ptr DeviceMemory) -> IO DeviceMemory)
-> IO DeviceMemory)
-> ContT DeviceMemory IO ("pMemory" ::: Ptr DeviceMemory)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMemory" ::: Ptr DeviceMemory) -> IO DeviceMemory)
-> IO DeviceMemory)
-> ContT DeviceMemory IO ("pMemory" ::: Ptr DeviceMemory))
-> ((("pMemory" ::: Ptr DeviceMemory) -> IO DeviceMemory)
-> IO DeviceMemory)
-> ContT DeviceMemory IO ("pMemory" ::: Ptr DeviceMemory)
forall a b. (a -> b) -> a -> b
$ IO ("pMemory" ::: Ptr DeviceMemory)
-> (("pMemory" ::: Ptr DeviceMemory) -> IO ())
-> (("pMemory" ::: Ptr DeviceMemory) -> IO DeviceMemory)
-> IO DeviceMemory
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("pMemory" ::: Ptr DeviceMemory)
forall a. Int -> IO (Ptr a)
callocBytes @DeviceMemory 8) ("pMemory" ::: Ptr DeviceMemory) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT DeviceMemory IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT DeviceMemory IO Result)
-> IO Result -> ContT DeviceMemory IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> ("pAllocateInfo" ::: Ptr (MemoryAllocateInfo a))
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> ("pMemory" ::: Ptr DeviceMemory)
-> IO Result
vkAllocateMemory' (Device -> Ptr Device_T
deviceHandle (Device
device)) "pAllocateInfo" ::: Ptr (MemoryAllocateInfo a)
pAllocateInfo "pAllocator" ::: Ptr AllocationCallbacks
pAllocator ("pMemory" ::: Ptr DeviceMemory
pPMemory)
IO () -> ContT DeviceMemory IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DeviceMemory IO ())
-> IO () -> ContT DeviceMemory 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))
DeviceMemory
pMemory <- IO DeviceMemory -> ContT DeviceMemory IO DeviceMemory
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO DeviceMemory -> ContT DeviceMemory IO DeviceMemory)
-> IO DeviceMemory -> ContT DeviceMemory IO DeviceMemory
forall a b. (a -> b) -> a -> b
$ ("pMemory" ::: Ptr DeviceMemory) -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory "pMemory" ::: Ptr DeviceMemory
pPMemory
DeviceMemory -> ContT DeviceMemory IO DeviceMemory
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceMemory -> ContT DeviceMemory IO DeviceMemory)
-> DeviceMemory -> ContT DeviceMemory IO DeviceMemory
forall a b. (a -> b) -> a -> b
$ (DeviceMemory
pMemory)
withMemory :: forall a io r . (Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) => Device -> MemoryAllocateInfo a -> Maybe AllocationCallbacks -> (io (DeviceMemory) -> ((DeviceMemory) -> io ()) -> r) -> r
withMemory :: Device
-> MemoryAllocateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> (io DeviceMemory -> (DeviceMemory -> io ()) -> r)
-> r
withMemory device :: Device
device pAllocateInfo :: MemoryAllocateInfo a
pAllocateInfo pAllocator :: "allocator" ::: Maybe AllocationCallbacks
pAllocator b :: io DeviceMemory -> (DeviceMemory -> io ()) -> r
b =
io DeviceMemory -> (DeviceMemory -> io ()) -> r
b (Device
-> MemoryAllocateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io DeviceMemory
forall (a :: [*]) (io :: * -> *).
(Extendss MemoryAllocateInfo a, PokeChain a, MonadIO io) =>
Device
-> MemoryAllocateInfo a
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io DeviceMemory
allocateMemory Device
device MemoryAllocateInfo a
pAllocateInfo "allocator" ::: Maybe AllocationCallbacks
pAllocator)
(\(DeviceMemory
o0) -> Device
-> DeviceMemory
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
forall (io :: * -> *).
MonadIO io =>
Device
-> DeviceMemory
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
freeMemory Device
device DeviceMemory
o0 "allocator" ::: Maybe AllocationCallbacks
pAllocator)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkFreeMemory
:: FunPtr (Ptr Device_T -> DeviceMemory -> Ptr AllocationCallbacks -> IO ()) -> Ptr Device_T -> DeviceMemory -> Ptr AllocationCallbacks -> IO ()
freeMemory :: forall io . MonadIO io => Device -> DeviceMemory -> ("allocator" ::: Maybe AllocationCallbacks) -> io ()
freeMemory :: Device
-> DeviceMemory
-> ("allocator" ::: Maybe AllocationCallbacks)
-> io ()
freeMemory device :: Device
device memory :: DeviceMemory
memory 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 vkFreeMemoryPtr :: FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkFreeMemoryPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
pVkFreeMemory (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
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkFreeMemoryPtr FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("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 vkFreeMemory is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkFreeMemory' :: Ptr Device_T
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkFreeMemory' = FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
-> Ptr Device_T
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
mkVkFreeMemory FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ())
vkFreeMemoryPtr
"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
-> DeviceMemory
-> ("pAllocator" ::: Ptr AllocationCallbacks)
-> IO ()
vkFreeMemory' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DeviceMemory
memory) "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" mkVkMapMemory
:: FunPtr (Ptr Device_T -> DeviceMemory -> DeviceSize -> DeviceSize -> MemoryMapFlags -> Ptr (Ptr ()) -> IO Result) -> Ptr Device_T -> DeviceMemory -> DeviceSize -> DeviceSize -> MemoryMapFlags -> Ptr (Ptr ()) -> IO Result
mapMemory :: forall io . MonadIO io => Device -> DeviceMemory -> ("offset" ::: DeviceSize) -> DeviceSize -> MemoryMapFlags -> io (("data" ::: Ptr ()))
mapMemory :: Device
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> io ("data" ::: Ptr ())
mapMemory device :: Device
device memory :: DeviceMemory
memory offset :: "offset" ::: DeviceSize
offset size :: "offset" ::: DeviceSize
size flags :: MemoryMapFlags
flags = IO ("data" ::: Ptr ()) -> io ("data" ::: Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("data" ::: Ptr ()) -> io ("data" ::: Ptr ()))
-> (ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ())
-> IO ("data" ::: Ptr ()))
-> ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ())
-> io ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ())
-> IO ("data" ::: Ptr ())
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ())
-> io ("data" ::: Ptr ()))
-> ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ())
-> io ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ do
let vkMapMemoryPtr :: FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result)
vkMapMemoryPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result)
pVkMapMemory (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT ("data" ::: Ptr ()) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("data" ::: Ptr ()) IO ())
-> IO () -> ContT ("data" ::: Ptr ()) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result)
vkMapMemoryPtr FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result)
-> FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: 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 vkMapMemory is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkMapMemory' :: Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result
vkMapMemory' = FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result)
-> Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result
mkVkMapMemory FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result)
vkMapMemoryPtr
"ppData" ::: Ptr ("data" ::: Ptr ())
pPpData <- ((("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO ("data" ::: Ptr ()))
-> IO ("data" ::: Ptr ()))
-> ContT
("data" ::: Ptr ()) IO ("ppData" ::: Ptr ("data" ::: Ptr ()))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO ("data" ::: Ptr ()))
-> IO ("data" ::: Ptr ()))
-> ContT
("data" ::: Ptr ()) IO ("ppData" ::: Ptr ("data" ::: Ptr ())))
-> ((("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO ("data" ::: Ptr ()))
-> IO ("data" ::: Ptr ()))
-> ContT
("data" ::: Ptr ()) IO ("ppData" ::: Ptr ("data" ::: Ptr ()))
forall a b. (a -> b) -> a -> b
$ IO ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> (("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO ())
-> (("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO ("data" ::: Ptr ()))
-> IO ("data" ::: Ptr ())
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO ("ppData" ::: Ptr ("data" ::: Ptr ()))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr ()) 8) ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT ("data" ::: Ptr ()) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT ("data" ::: Ptr ()) IO Result)
-> IO Result -> ContT ("data" ::: Ptr ()) IO Result
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> IO Result
vkMapMemory' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DeviceMemory
memory) ("offset" ::: DeviceSize
offset) ("offset" ::: DeviceSize
size) (MemoryMapFlags
flags) ("ppData" ::: Ptr ("data" ::: Ptr ())
pPpData)
IO () -> ContT ("data" ::: Ptr ()) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("data" ::: Ptr ()) IO ())
-> IO () -> ContT ("data" ::: Ptr ()) 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" ::: Ptr ()
ppData <- IO ("data" ::: Ptr ())
-> ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ())
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("data" ::: Ptr ())
-> ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ()))
-> IO ("data" ::: Ptr ())
-> ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO ("data" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) "ppData" ::: Ptr ("data" ::: Ptr ())
pPpData
("data" ::: Ptr ())
-> ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("data" ::: Ptr ())
-> ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ()))
-> ("data" ::: Ptr ())
-> ContT ("data" ::: Ptr ()) IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ ("data" ::: Ptr ()
ppData)
withMappedMemory :: forall io r . MonadIO io => Device -> DeviceMemory -> DeviceSize -> DeviceSize -> MemoryMapFlags -> (io (Ptr ()) -> ((Ptr ()) -> io ()) -> r) -> r
withMappedMemory :: Device
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> (io ("data" ::: Ptr ()) -> (("data" ::: Ptr ()) -> io ()) -> r)
-> r
withMappedMemory device :: Device
device memory :: DeviceMemory
memory offset :: "offset" ::: DeviceSize
offset size :: "offset" ::: DeviceSize
size flags :: MemoryMapFlags
flags b :: io ("data" ::: Ptr ()) -> (("data" ::: Ptr ()) -> io ()) -> r
b =
io ("data" ::: Ptr ()) -> (("data" ::: Ptr ()) -> io ()) -> r
b (Device
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> io ("data" ::: Ptr ())
forall (io :: * -> *).
MonadIO io =>
Device
-> DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MemoryMapFlags
-> io ("data" ::: Ptr ())
mapMemory Device
device DeviceMemory
memory "offset" ::: DeviceSize
offset "offset" ::: DeviceSize
size MemoryMapFlags
flags)
(\("data" ::: Ptr ()
_) -> Device -> DeviceMemory -> io ()
forall (io :: * -> *).
MonadIO io =>
Device -> DeviceMemory -> io ()
unmapMemory Device
device DeviceMemory
memory)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkUnmapMemory
:: FunPtr (Ptr Device_T -> DeviceMemory -> IO ()) -> Ptr Device_T -> DeviceMemory -> IO ()
unmapMemory :: forall io . MonadIO io => Device -> DeviceMemory -> io ()
unmapMemory :: Device -> DeviceMemory -> io ()
unmapMemory device :: Device
device memory :: DeviceMemory
memory = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
let vkUnmapMemoryPtr :: FunPtr (Ptr Device_T -> DeviceMemory -> IO ())
vkUnmapMemoryPtr = DeviceCmds -> FunPtr (Ptr Device_T -> DeviceMemory -> IO ())
pVkUnmapMemory (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr (Ptr Device_T -> DeviceMemory -> IO ())
vkUnmapMemoryPtr FunPtr (Ptr Device_T -> DeviceMemory -> IO ())
-> FunPtr (Ptr Device_T -> DeviceMemory -> IO ()) -> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr (Ptr Device_T -> DeviceMemory -> 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 vkUnmapMemory is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkUnmapMemory' :: Ptr Device_T -> DeviceMemory -> IO ()
vkUnmapMemory' = FunPtr (Ptr Device_T -> DeviceMemory -> IO ())
-> Ptr Device_T -> DeviceMemory -> IO ()
mkVkUnmapMemory FunPtr (Ptr Device_T -> DeviceMemory -> IO ())
vkUnmapMemoryPtr
Ptr Device_T -> DeviceMemory -> IO ()
vkUnmapMemory' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DeviceMemory
memory)
() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkFlushMappedMemoryRanges
:: FunPtr (Ptr Device_T -> Word32 -> Ptr MappedMemoryRange -> IO Result) -> Ptr Device_T -> Word32 -> Ptr MappedMemoryRange -> IO Result
flushMappedMemoryRanges :: forall io . MonadIO io => Device -> ("memoryRanges" ::: Vector MappedMemoryRange) -> io ()
flushMappedMemoryRanges :: Device -> ("memoryRanges" ::: Vector MappedMemoryRange) -> io ()
flushMappedMemoryRanges device :: Device
device memoryRanges :: "memoryRanges" ::: Vector MappedMemoryRange
memoryRanges = 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 vkFlushMappedMemoryRangesPtr :: FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
vkFlushMappedMemoryRangesPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
pVkFlushMappedMemoryRanges (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
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
vkFlushMappedMemoryRangesPtr FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> 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 vkFlushMappedMemoryRanges is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkFlushMappedMemoryRanges' :: Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result
vkFlushMappedMemoryRanges' = FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
-> Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result
mkVkFlushMappedMemoryRanges FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
vkFlushMappedMemoryRangesPtr
"pMemoryRanges" ::: Ptr MappedMemoryRange
pPMemoryRanges <- ((("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO ()) -> IO ())
-> ContT () IO ("pMemoryRanges" ::: Ptr MappedMemoryRange)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO ()) -> IO ())
-> ContT () IO ("pMemoryRanges" ::: Ptr MappedMemoryRange))
-> ((("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO ())
-> IO ())
-> ContT () IO ("pMemoryRanges" ::: Ptr MappedMemoryRange)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @MappedMemoryRange ((("memoryRanges" ::: Vector MappedMemoryRange) -> Int
forall a. Vector a -> Int
Data.Vector.length ("memoryRanges" ::: Vector MappedMemoryRange
memoryRanges)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
(Int -> MappedMemoryRange -> ContT () IO ())
-> ("memoryRanges" ::: Vector MappedMemoryRange) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: MappedMemoryRange
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> MappedMemoryRange -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pMemoryRanges" ::: Ptr MappedMemoryRange
pPMemoryRanges ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int -> "pMemoryRanges" ::: Ptr MappedMemoryRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MappedMemoryRange) (MappedMemoryRange
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("memoryRanges" ::: Vector MappedMemoryRange
memoryRanges)
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
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result
vkFlushMappedMemoryRanges' (Device -> Ptr Device_T
deviceHandle (Device
device)) ((Int -> "memoryRangeCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("memoryRanges" ::: Vector MappedMemoryRange) -> Int
forall a. Vector a -> Int
Data.Vector.length (("memoryRanges" ::: Vector MappedMemoryRange) -> Int)
-> ("memoryRanges" ::: Vector MappedMemoryRange) -> Int
forall a b. (a -> b) -> a -> b
$ ("memoryRanges" ::: Vector MappedMemoryRange
memoryRanges)) :: Word32)) ("pMemoryRanges" ::: Ptr MappedMemoryRange
pPMemoryRanges)
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkInvalidateMappedMemoryRanges
:: FunPtr (Ptr Device_T -> Word32 -> Ptr MappedMemoryRange -> IO Result) -> Ptr Device_T -> Word32 -> Ptr MappedMemoryRange -> IO Result
invalidateMappedMemoryRanges :: forall io . MonadIO io => Device -> ("memoryRanges" ::: Vector MappedMemoryRange) -> io ()
invalidateMappedMemoryRanges :: Device -> ("memoryRanges" ::: Vector MappedMemoryRange) -> io ()
invalidateMappedMemoryRanges device :: Device
device memoryRanges :: "memoryRanges" ::: Vector MappedMemoryRange
memoryRanges = 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 vkInvalidateMappedMemoryRangesPtr :: FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
vkInvalidateMappedMemoryRangesPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
pVkInvalidateMappedMemoryRanges (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
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
vkInvalidateMappedMemoryRangesPtr FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
-> FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> 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 vkInvalidateMappedMemoryRanges is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkInvalidateMappedMemoryRanges' :: Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result
vkInvalidateMappedMemoryRanges' = FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
-> Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result
mkVkInvalidateMappedMemoryRanges FunPtr
(Ptr Device_T
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result)
vkInvalidateMappedMemoryRangesPtr
"pMemoryRanges" ::: Ptr MappedMemoryRange
pPMemoryRanges <- ((("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO ()) -> IO ())
-> ContT () IO ("pMemoryRanges" ::: Ptr MappedMemoryRange)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO ()) -> IO ())
-> ContT () IO ("pMemoryRanges" ::: Ptr MappedMemoryRange))
-> ((("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO ())
-> IO ())
-> ContT () IO ("pMemoryRanges" ::: Ptr MappedMemoryRange)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @MappedMemoryRange ((("memoryRanges" ::: Vector MappedMemoryRange) -> Int
forall a. Vector a -> Int
Data.Vector.length ("memoryRanges" ::: Vector MappedMemoryRange
memoryRanges)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
(Int -> MappedMemoryRange -> ContT () IO ())
-> ("memoryRanges" ::: Vector MappedMemoryRange) -> ContT () IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: MappedMemoryRange
e -> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((() -> IO ()) -> IO ()) -> ContT () IO ())
-> ((() -> IO ()) -> IO ()) -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> MappedMemoryRange -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct ("pMemoryRanges" ::: Ptr MappedMemoryRange
pPMemoryRanges ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int -> "pMemoryRanges" ::: Ptr MappedMemoryRange
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MappedMemoryRange) (MappedMemoryRange
e) (IO () -> IO ())
-> ((() -> IO ()) -> IO ()) -> (() -> IO ()) -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ())) ("memoryRanges" ::: Vector MappedMemoryRange
memoryRanges)
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
-> ("memoryRangeCount" ::: Word32)
-> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> IO Result
vkInvalidateMappedMemoryRanges' (Device -> Ptr Device_T
deviceHandle (Device
device)) ((Int -> "memoryRangeCount" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("memoryRanges" ::: Vector MappedMemoryRange) -> Int
forall a. Vector a -> Int
Data.Vector.length (("memoryRanges" ::: Vector MappedMemoryRange) -> Int)
-> ("memoryRanges" ::: Vector MappedMemoryRange) -> Int
forall a b. (a -> b) -> a -> b
$ ("memoryRanges" ::: Vector MappedMemoryRange
memoryRanges)) :: Word32)) ("pMemoryRanges" ::: Ptr MappedMemoryRange
pPMemoryRanges)
IO () -> ContT () IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT () IO ()) -> IO () -> ContT () IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Result
r Result -> Result -> Bool
forall a. Ord a => a -> a -> Bool
< Result
SUCCESS) (VulkanException -> IO ()
forall e a. Exception e => e -> IO a
throwIO (Result -> VulkanException
VulkanException Result
r))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"dynamic" mkVkGetDeviceMemoryCommitment
:: FunPtr (Ptr Device_T -> DeviceMemory -> Ptr DeviceSize -> IO ()) -> Ptr Device_T -> DeviceMemory -> Ptr DeviceSize -> IO ()
getDeviceMemoryCommitment :: forall io . MonadIO io => Device -> DeviceMemory -> io (("committedMemoryInBytes" ::: DeviceSize))
getDeviceMemoryCommitment :: Device -> DeviceMemory -> io ("offset" ::: DeviceSize)
getDeviceMemoryCommitment device :: Device
device memory :: DeviceMemory
memory = IO ("offset" ::: DeviceSize) -> io ("offset" ::: DeviceSize)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("offset" ::: DeviceSize) -> io ("offset" ::: DeviceSize))
-> (ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize)
-> IO ("offset" ::: DeviceSize))
-> ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize)
-> io ("offset" ::: DeviceSize)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize)
-> IO ("offset" ::: DeviceSize)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize)
-> io ("offset" ::: DeviceSize))
-> ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize)
-> io ("offset" ::: DeviceSize)
forall a b. (a -> b) -> a -> b
$ do
let vkGetDeviceMemoryCommitmentPtr :: FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ())
vkGetDeviceMemoryCommitmentPtr = DeviceCmds
-> FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ())
pVkGetDeviceMemoryCommitment (Device -> DeviceCmds
deviceCmds (Device
device :: Device))
IO () -> ContT ("offset" ::: DeviceSize) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("offset" ::: DeviceSize) IO ())
-> IO () -> ContT ("offset" ::: DeviceSize) IO ()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ())
vkGetDeviceMemoryCommitmentPtr FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ())
-> FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ())
-> Bool
forall a. Eq a => a -> a -> Bool
/= FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> 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 vkGetDeviceMemoryCommitment is null" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let vkGetDeviceMemoryCommitment' :: Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ()
vkGetDeviceMemoryCommitment' = FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ())
-> Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ()
mkVkGetDeviceMemoryCommitment FunPtr
(Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ())
vkGetDeviceMemoryCommitmentPtr
"pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
pPCommittedMemoryInBytes <- ((("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize))
-> ContT
("offset" ::: DeviceSize)
IO
("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize))
-> ContT
("offset" ::: DeviceSize)
IO
("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)))
-> ((("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize))
-> ContT
("offset" ::: DeviceSize)
IO
("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
forall a b. (a -> b) -> a -> b
$ IO ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> (("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ())
-> (("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int
-> IO ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
forall a. Int -> IO (Ptr a)
callocBytes @DeviceSize 8) ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ()
forall a. Ptr a -> IO ()
free
IO () -> ContT ("offset" ::: DeviceSize) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("offset" ::: DeviceSize) IO ())
-> IO () -> ContT ("offset" ::: DeviceSize) IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Device_T
-> DeviceMemory
-> ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ()
vkGetDeviceMemoryCommitment' (Device -> Ptr Device_T
deviceHandle (Device
device)) (DeviceMemory
memory) ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
pPCommittedMemoryInBytes)
"offset" ::: DeviceSize
pCommittedMemoryInBytes <- IO ("offset" ::: DeviceSize)
-> ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("offset" ::: DeviceSize)
-> ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
-> ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize)
forall a b. (a -> b) -> a -> b
$ ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
pPCommittedMemoryInBytes
("offset" ::: DeviceSize)
-> ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("offset" ::: DeviceSize)
-> ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize)
-> ContT ("offset" ::: DeviceSize) IO ("offset" ::: DeviceSize)
forall a b. (a -> b) -> a -> b
$ ("offset" ::: DeviceSize
pCommittedMemoryInBytes)
data MemoryAllocateInfo (es :: [Type]) = MemoryAllocateInfo
{
MemoryAllocateInfo es -> Chain es
next :: Chain es
,
MemoryAllocateInfo es -> "offset" ::: DeviceSize
allocationSize :: DeviceSize
,
MemoryAllocateInfo es -> "memoryRangeCount" ::: Word32
memoryTypeIndex :: Word32
}
deriving (Typeable)
deriving instance Show (Chain es) => Show (MemoryAllocateInfo es)
instance Extensible MemoryAllocateInfo where
extensibleType :: StructureType
extensibleType = StructureType
STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO
setNext :: MemoryAllocateInfo ds -> Chain es -> MemoryAllocateInfo es
setNext x :: MemoryAllocateInfo ds
x next :: Chain es
next = MemoryAllocateInfo ds
x{$sel:next:MemoryAllocateInfo :: Chain es
next = Chain es
next}
getNext :: MemoryAllocateInfo es -> Chain es
getNext MemoryAllocateInfo{..} = Chain es
next
extends :: forall e b proxy. Typeable e => proxy e -> (Extends MemoryAllocateInfo e => b) -> Maybe b
extends :: proxy e -> (Extends MemoryAllocateInfo e => b) -> Maybe b
extends _ f :: Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable MemoryOpaqueCaptureAddressAllocateInfo) =>
Maybe (e :~: MemoryOpaqueCaptureAddressAllocateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @MemoryOpaqueCaptureAddressAllocateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable MemoryPriorityAllocateInfoEXT) =>
Maybe (e :~: MemoryPriorityAllocateInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @MemoryPriorityAllocateInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImportAndroidHardwareBufferInfoANDROID) =>
Maybe (e :~: ImportAndroidHardwareBufferInfoANDROID)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImportAndroidHardwareBufferInfoANDROID = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImportMemoryHostPointerInfoEXT) =>
Maybe (e :~: ImportMemoryHostPointerInfoEXT)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImportMemoryHostPointerInfoEXT = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable MemoryDedicatedAllocateInfo) =>
Maybe (e :~: MemoryDedicatedAllocateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @MemoryDedicatedAllocateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable MemoryAllocateFlagsInfo) =>
Maybe (e :~: MemoryAllocateFlagsInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @MemoryAllocateFlagsInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImportMemoryFdInfoKHR) =>
Maybe (e :~: ImportMemoryFdInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImportMemoryFdInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ExportMemoryWin32HandleInfoKHR) =>
Maybe (e :~: ExportMemoryWin32HandleInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExportMemoryWin32HandleInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImportMemoryWin32HandleInfoKHR) =>
Maybe (e :~: ImportMemoryWin32HandleInfoKHR)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImportMemoryWin32HandleInfoKHR = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ExportMemoryAllocateInfo) =>
Maybe (e :~: ExportMemoryAllocateInfo)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExportMemoryAllocateInfo = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ExportMemoryWin32HandleInfoNV) =>
Maybe (e :~: ExportMemoryWin32HandleInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExportMemoryWin32HandleInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ImportMemoryWin32HandleInfoNV) =>
Maybe (e :~: ImportMemoryWin32HandleInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ImportMemoryWin32HandleInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable ExportMemoryAllocateInfoNV) =>
Maybe (e :~: ExportMemoryAllocateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @ExportMemoryAllocateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Just Refl <- (Typeable e, Typeable DedicatedAllocationMemoryAllocateInfoNV) =>
Maybe (e :~: DedicatedAllocationMemoryAllocateInfoNV)
forall k (a :: k) (b :: k).
(Typeable a, Typeable b) =>
Maybe (a :~: b)
eqT @e @DedicatedAllocationMemoryAllocateInfoNV = b -> Maybe b
forall a. a -> Maybe a
Just b
Extends MemoryAllocateInfo e => b
f
| Bool
otherwise = Maybe b
forall a. Maybe a
Nothing
instance (Extendss MemoryAllocateInfo es, PokeChain es) => ToCStruct (MemoryAllocateInfo es) where
withCStruct :: MemoryAllocateInfo es
-> (Ptr (MemoryAllocateInfo es) -> IO b) -> IO b
withCStruct x :: MemoryAllocateInfo es
x f :: Ptr (MemoryAllocateInfo es) -> IO b
f = Int -> Int -> (Ptr (MemoryAllocateInfo es) -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr (MemoryAllocateInfo es) -> IO b) -> IO b)
-> (Ptr (MemoryAllocateInfo es) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr (MemoryAllocateInfo es)
p -> Ptr (MemoryAllocateInfo es)
-> MemoryAllocateInfo es -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr (MemoryAllocateInfo es)
p MemoryAllocateInfo es
x (Ptr (MemoryAllocateInfo es) -> IO b
f Ptr (MemoryAllocateInfo es)
p)
pokeCStruct :: Ptr (MemoryAllocateInfo es)
-> MemoryAllocateInfo es -> IO b -> IO b
pokeCStruct p :: Ptr (MemoryAllocateInfo es)
p MemoryAllocateInfo{..} f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO)
"data" ::: Ptr ()
pNext'' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ Chain es -> (Ptr (Chain es) -> IO b) -> IO b
forall (es :: [*]) a.
PokeChain es =>
Chain es -> (Ptr (Chain es) -> IO a) -> IO a
withChain (Chain es
next)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es)
-> Int -> "ppData" ::: Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext''
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es)
-> Int
-> "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
allocationSize)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("memoryRangeCount" ::: Word32)
-> ("memoryRangeCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es)
-> Int -> Ptr ("memoryRangeCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("memoryRangeCount" ::: Word32
memoryTypeIndex)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
cStructSize :: Int
cStructSize = 32
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr (MemoryAllocateInfo es) -> IO b -> IO b
pokeZeroCStruct p :: Ptr (MemoryAllocateInfo es)
p f :: IO b
f = ContT b IO b -> IO b
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT b IO b -> IO b) -> ContT b IO b -> IO b
forall a b. (a -> b) -> a -> b
$ do
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es) -> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MEMORY_ALLOCATE_INFO)
"data" ::: Ptr ()
pNext' <- (Ptr (Chain es) -> "data" ::: Ptr ())
-> ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Ptr (Chain es) -> "data" ::: Ptr ()
forall a b. Ptr a -> Ptr b
castPtr (ContT b IO (Ptr (Chain es)) -> ContT b IO ("data" ::: Ptr ()))
-> (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO (Ptr (Chain es)))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Ptr (Chain es) -> IO b) -> IO b) -> ContT b IO (Ptr (Chain es))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ()))
-> ((Ptr (Chain es) -> IO b) -> IO b)
-> ContT b IO ("data" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ forall a. PokeChain es => (Ptr (Chain es) -> IO a) -> IO a
forall (es :: [*]) a.
PokeChain es =>
(Ptr (Chain es) -> IO a) -> IO a
withZeroChain @es
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("ppData" ::: Ptr ("data" ::: Ptr ()))
-> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es)
-> Int -> "ppData" ::: Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) "data" ::: Ptr ()
pNext'
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es)
-> Int
-> "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
forall a. Zero a => a
zero)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr ("memoryRangeCount" ::: Word32)
-> ("memoryRangeCount" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es)
-> Int -> Ptr ("memoryRangeCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ("memoryRangeCount" ::: Word32
forall a. Zero a => a
zero)
IO b -> ContT b IO b
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO b -> ContT b IO b) -> IO b -> ContT b IO b
forall a b. (a -> b) -> a -> b
$ IO b
f
instance (Extendss MemoryAllocateInfo es, PeekChain es) => FromCStruct (MemoryAllocateInfo es) where
peekCStruct :: Ptr (MemoryAllocateInfo es) -> IO (MemoryAllocateInfo es)
peekCStruct p :: Ptr (MemoryAllocateInfo es)
p = do
"data" ::: Ptr ()
pNext <- ("ppData" ::: Ptr ("data" ::: Ptr ())) -> IO ("data" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es)
-> Int -> "ppData" ::: Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ())))
Chain es
next <- Ptr (Chain es) -> IO (Chain es)
forall (es :: [*]). PeekChain es => Ptr (Chain es) -> IO (Chain es)
peekChain (("data" ::: Ptr ()) -> Ptr (Chain es)
forall a b. Ptr a -> Ptr b
castPtr "data" ::: Ptr ()
pNext)
"offset" ::: DeviceSize
allocationSize <- ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es)
-> Int
-> "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
"memoryRangeCount" ::: Word32
memoryTypeIndex <- Ptr ("memoryRangeCount" ::: Word32)
-> IO ("memoryRangeCount" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr (MemoryAllocateInfo es)
p Ptr (MemoryAllocateInfo es)
-> Int -> Ptr ("memoryRangeCount" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
MemoryAllocateInfo es -> IO (MemoryAllocateInfo es)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryAllocateInfo es -> IO (MemoryAllocateInfo es))
-> MemoryAllocateInfo es -> IO (MemoryAllocateInfo es)
forall a b. (a -> b) -> a -> b
$ Chain es
-> ("offset" ::: DeviceSize)
-> ("memoryRangeCount" ::: Word32)
-> MemoryAllocateInfo es
forall (es :: [*]).
Chain es
-> ("offset" ::: DeviceSize)
-> ("memoryRangeCount" ::: Word32)
-> MemoryAllocateInfo es
MemoryAllocateInfo
Chain es
next "offset" ::: DeviceSize
allocationSize "memoryRangeCount" ::: Word32
memoryTypeIndex
instance es ~ '[] => Zero (MemoryAllocateInfo es) where
zero :: MemoryAllocateInfo es
zero = Chain es
-> ("offset" ::: DeviceSize)
-> ("memoryRangeCount" ::: Word32)
-> MemoryAllocateInfo es
forall (es :: [*]).
Chain es
-> ("offset" ::: DeviceSize)
-> ("memoryRangeCount" ::: Word32)
-> MemoryAllocateInfo es
MemoryAllocateInfo
()
"offset" ::: DeviceSize
forall a. Zero a => a
zero
"memoryRangeCount" ::: Word32
forall a. Zero a => a
zero
data MappedMemoryRange = MappedMemoryRange
{
MappedMemoryRange -> DeviceMemory
memory :: DeviceMemory
,
MappedMemoryRange -> "offset" ::: DeviceSize
offset :: DeviceSize
,
MappedMemoryRange -> "offset" ::: DeviceSize
size :: DeviceSize
}
deriving (Typeable)
deriving instance Show MappedMemoryRange
instance ToCStruct MappedMemoryRange where
withCStruct :: MappedMemoryRange
-> (("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b) -> IO b
withCStruct x :: MappedMemoryRange
x f :: ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b
f = Int
-> Int
-> (("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b)
-> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b) -> IO b)
-> (("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: "pMemoryRanges" ::: Ptr MappedMemoryRange
p -> ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> MappedMemoryRange -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryRanges" ::: Ptr MappedMemoryRange
p MappedMemoryRange
x (("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b
f "pMemoryRanges" ::: Ptr MappedMemoryRange
p)
pokeCStruct :: ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> MappedMemoryRange -> IO b -> IO b
pokeCStruct p :: "pMemoryRanges" ::: Ptr MappedMemoryRange
p MappedMemoryRange{..} f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MAPPED_MEMORY_RANGE)
("ppData" ::: Ptr ("data" ::: Ptr ()))
-> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int -> "ppData" ::: Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
("pMemory" ::: Ptr DeviceMemory) -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int -> "pMemory" ::: Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceMemory)) (DeviceMemory
memory)
("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int
-> "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
offset)
("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int
-> "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
size)
IO b
f
cStructSize :: Int
cStructSize = 40
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO b -> IO b
pokeZeroCStruct p :: "pMemoryRanges" ::: Ptr MappedMemoryRange
p f :: IO b
f = do
Ptr StructureType -> StructureType -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int -> Ptr StructureType
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr StructureType)) (StructureType
STRUCTURE_TYPE_MAPPED_MEMORY_RANGE)
("ppData" ::: Ptr ("data" ::: Ptr ()))
-> ("data" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int -> "ppData" ::: Ptr ("data" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr ()))) ("data" ::: Ptr ()
forall a. Ptr a
nullPtr)
("pMemory" ::: Ptr DeviceMemory) -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int -> "pMemory" ::: Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceMemory)) (DeviceMemory
forall a. Zero a => a
zero)
("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int
-> "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
forall a. Zero a => a
zero)
("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> ("offset" ::: DeviceSize) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int
-> "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) ("offset" ::: DeviceSize
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct MappedMemoryRange where
peekCStruct :: ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO MappedMemoryRange
peekCStruct p :: "pMemoryRanges" ::: Ptr MappedMemoryRange
p = do
DeviceMemory
memory <- ("pMemory" ::: Ptr DeviceMemory) -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int -> "pMemory" ::: Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceMemory))
"offset" ::: DeviceSize
offset <- ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int
-> "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
"offset" ::: DeviceSize
size <- ("pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize))
-> IO ("offset" ::: DeviceSize)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize (("pMemoryRanges" ::: Ptr MappedMemoryRange
p ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> Int
-> "pCommittedMemoryInBytes" ::: Ptr ("offset" ::: DeviceSize)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize))
MappedMemoryRange -> IO MappedMemoryRange
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MappedMemoryRange -> IO MappedMemoryRange)
-> MappedMemoryRange -> IO MappedMemoryRange
forall a b. (a -> b) -> a -> b
$ DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MappedMemoryRange
MappedMemoryRange
DeviceMemory
memory "offset" ::: DeviceSize
offset "offset" ::: DeviceSize
size
instance Storable MappedMemoryRange where
sizeOf :: MappedMemoryRange -> Int
sizeOf ~MappedMemoryRange
_ = 40
alignment :: MappedMemoryRange -> Int
alignment ~MappedMemoryRange
_ = 8
peek :: ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO MappedMemoryRange
peek = ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO MappedMemoryRange
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> MappedMemoryRange -> IO ()
poke ptr :: "pMemoryRanges" ::: Ptr MappedMemoryRange
ptr poked :: MappedMemoryRange
poked = ("pMemoryRanges" ::: Ptr MappedMemoryRange)
-> MappedMemoryRange -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct "pMemoryRanges" ::: Ptr MappedMemoryRange
ptr MappedMemoryRange
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero MappedMemoryRange where
zero :: MappedMemoryRange
zero = DeviceMemory
-> ("offset" ::: DeviceSize)
-> ("offset" ::: DeviceSize)
-> MappedMemoryRange
MappedMemoryRange
DeviceMemory
forall a. Zero a => a
zero
"offset" ::: DeviceSize
forall a. Zero a => a
zero
"offset" ::: DeviceSize
forall a. Zero a => a
zero