{-# language CPP #-}
module VulkanMemoryAllocator ( createAllocator
, withAllocator
, destroyAllocator
, getAllocatorInfo
, getPhysicalDeviceProperties
, getMemoryProperties
, getMemoryTypeProperties
, setCurrentFrameIndex
, calculateStats
, getBudget
, buildStatsString
, freeStatsString
, findMemoryTypeIndex
, findMemoryTypeIndexForBufferInfo
, findMemoryTypeIndexForImageInfo
, createPool
, withPool
, destroyPool
, getPoolStats
, makePoolAllocationsLost
, checkPoolCorruption
, getPoolName
, setPoolName
, allocateMemory
, withMemory
, allocateMemoryPages
, withMemoryPages
, allocateMemoryForBuffer
, withMemoryForBuffer
, allocateMemoryForImage
, withMemoryForImage
, freeMemory
, freeMemoryPages
, resizeAllocation
, getAllocationInfo
, touchAllocation
, setAllocationUserData
, createLostAllocation
, withLostAllocation
, mapMemory
, withMappedMemory
, unmapMemory
, flushAllocation
, invalidateAllocation
, flushAllocations
, invalidateAllocations
, checkCorruption
, defragmentationBegin
, withDefragmentation
, defragmentationEnd
, beginDefragmentationPass
, useDefragmentationPass
, endDefragmentationPass
, defragment
, bindBufferMemory
, bindBufferMemory2
, bindImageMemory
, bindImageMemory2
, createBuffer
, withBuffer
, destroyBuffer
, createImage
, withImage
, destroyImage
, Allocator(..)
, PFN_vmaAllocateDeviceMemoryFunction
, FN_vmaAllocateDeviceMemoryFunction
, PFN_vmaFreeDeviceMemoryFunction
, FN_vmaFreeDeviceMemoryFunction
, DeviceMemoryCallbacks(..)
, AllocatorCreateFlagBits( ALLOCATOR_CREATE_EXTERNALLY_SYNCHRONIZED_BIT
, ALLOCATOR_CREATE_KHR_DEDICATED_ALLOCATION_BIT
, ALLOCATOR_CREATE_KHR_BIND_MEMORY2_BIT
, ALLOCATOR_CREATE_EXT_MEMORY_BUDGET_BIT
, ALLOCATOR_CREATE_AMD_DEVICE_COHERENT_MEMORY_BIT
, ALLOCATOR_CREATE_BUFFER_DEVICE_ADDRESS_BIT
, ..
)
, AllocatorCreateFlags
, VulkanFunctions(..)
, RecordFlagBits( RECORD_FLUSH_AFTER_CALL_BIT
, ..
)
, RecordFlags
, RecordSettings(..)
, AllocatorCreateInfo(..)
, AllocatorInfo(..)
, StatInfo(..)
, Stats(..)
, Budget(..)
, Pool(..)
, MemoryUsage( MEMORY_USAGE_UNKNOWN
, MEMORY_USAGE_GPU_ONLY
, MEMORY_USAGE_CPU_ONLY
, MEMORY_USAGE_CPU_TO_GPU
, MEMORY_USAGE_GPU_TO_CPU
, MEMORY_USAGE_CPU_COPY
, MEMORY_USAGE_GPU_LAZILY_ALLOCATED
, ..
)
, AllocationCreateFlagBits( ALLOCATION_CREATE_DEDICATED_MEMORY_BIT
, ALLOCATION_CREATE_NEVER_ALLOCATE_BIT
, ALLOCATION_CREATE_MAPPED_BIT
, ALLOCATION_CREATE_CAN_BECOME_LOST_BIT
, ALLOCATION_CREATE_CAN_MAKE_OTHER_LOST_BIT
, ALLOCATION_CREATE_USER_DATA_COPY_STRING_BIT
, ALLOCATION_CREATE_UPPER_ADDRESS_BIT
, ALLOCATION_CREATE_DONT_BIND_BIT
, ALLOCATION_CREATE_WITHIN_BUDGET_BIT
, ALLOCATION_CREATE_STRATEGY_BEST_FIT_BIT
, ALLOCATION_CREATE_STRATEGY_WORST_FIT_BIT
, ALLOCATION_CREATE_STRATEGY_FIRST_FIT_BIT
, ALLOCATION_CREATE_STRATEGY_MIN_MEMORY_BIT
, ALLOCATION_CREATE_STRATEGY_MIN_TIME_BIT
, ALLOCATION_CREATE_STRATEGY_MIN_FRAGMENTATION_BIT
, ALLOCATION_CREATE_STRATEGY_MASK
, ..
)
, AllocationCreateFlags
, AllocationCreateInfo(..)
, PoolCreateFlagBits( POOL_CREATE_IGNORE_BUFFER_IMAGE_GRANULARITY_BIT
, POOL_CREATE_LINEAR_ALGORITHM_BIT
, POOL_CREATE_BUDDY_ALGORITHM_BIT
, POOL_CREATE_ALGORITHM_MASK
, ..
)
, PoolCreateFlags
, PoolCreateInfo(..)
, PoolStats(..)
, Allocation(..)
, AllocationInfo(..)
, DefragmentationContext(..)
, DefragmentationFlagBits( DEFRAGMENTATION_FLAG_INCREMENTAL
, ..
)
, DefragmentationFlags
, DefragmentationInfo2(..)
, DefragmentationPassMoveInfo(..)
, DefragmentationPassInfo(..)
, DefragmentationInfo(..)
, DefragmentationStats(..)
) where
import Vulkan (AllocationCallbacks)
import Vulkan (BindBufferMemoryInfo)
import Vulkan (BindImageMemoryInfo)
import Vulkan (Bool32)
import Vulkan (Buffer)
import Vulkan (BufferCopy)
import Vulkan (BufferCreateInfo)
import Vulkan (BufferMemoryRequirementsInfo2)
import Vulkan (CommandBuffer_T)
import Vulkan (DeviceMemory)
import Vulkan (DeviceSize)
import Vulkan (Device_T)
import Vulkan (Flags)
import Vulkan (Image)
import Vulkan (ImageCreateInfo)
import Vulkan (ImageMemoryRequirementsInfo2)
import Vulkan (Instance_T)
import Vulkan (MappedMemoryRange)
import Vulkan (MemoryAllocateInfo)
import Vulkan (MemoryMapFlags)
import Vulkan (MemoryPropertyFlags)
import Vulkan (MemoryRequirements)
import Vulkan (MemoryRequirements2)
import Vulkan (PhysicalDeviceMemoryProperties)
import Vulkan (PhysicalDeviceMemoryProperties2)
import Vulkan (PhysicalDeviceProperties)
import Vulkan (PhysicalDevice_T)
import Vulkan (Result)
import Vulkan.CStruct.Utils (FixedArray)
import Vulkan.CStruct.Extends (forgetExtensions)
import Vulkan.CStruct.Utils (advancePtrBytes)
import Vulkan.CStruct.Utils (lowerArrayPtr)
import Vulkan.Core10.BaseType (bool32ToBool)
import Vulkan.Core10.BaseType (boolToBool32)
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 Foreign.Marshal.Utils (maybePeek)
import GHC.Base (when)
import GHC.IO (throwIO)
import Foreign.Ptr (nullPtr)
import Foreign.Ptr (plusPtr)
import GHC.Read (choose)
import GHC.Read (expectP)
import GHC.Read (parens)
import GHC.Show (showParen)
import GHC.Show (showString)
import GHC.Show (showsPrec)
import Numeric (showHex)
import Text.ParserCombinators.ReadPrec ((+++))
import Text.ParserCombinators.ReadPrec (prec)
import Text.ParserCombinators.ReadPrec (step)
import Data.ByteString (packCString)
import Data.ByteString (useAsCString)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Cont (evalContT)
import Data.Vector (generateM)
import qualified Data.Vector (imapM_)
import qualified Data.Vector (length)
import qualified Data.Vector (null)
import Vulkan.Core10.APIConstants (pattern MAX_MEMORY_HEAPS)
import Vulkan.Core10.APIConstants (pattern MAX_MEMORY_TYPES)
import Vulkan.Core10.Enums.Result (pattern SUCCESS)
import Foreign.C.Types (CChar(..))
import Foreign.C.Types (CSize(..))
import Vulkan (Bool32(..))
import Vulkan (Buffer(..))
import Vulkan (Image(..))
import Vulkan (MemoryPropertyFlagBits(..))
import Vulkan (Result(..))
import Vulkan.CStruct (FromCStruct)
import Vulkan.CStruct (FromCStruct(..))
import Vulkan.CStruct (ToCStruct)
import Vulkan.CStruct (ToCStruct(..))
import Vulkan.CStruct.Extends (Extendss)
import Vulkan.CStruct.Extends (PokeChain)
import Vulkan.CStruct.Extends (SomeStruct)
import Vulkan.Core10.APIConstants (IsHandle)
import Vulkan.Core10.APIConstants (MAX_MEMORY_HEAPS)
import Vulkan.Core10.APIConstants (MAX_MEMORY_TYPES)
import Vulkan.Exception (VulkanException(..))
import Vulkan.NamedType ((:::))
import Vulkan.Zero (Zero)
import Vulkan.Zero (Zero(..))
import Control.Monad.IO.Class (MonadIO)
import Data.Bits (Bits)
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.Generics (Generic)
import GHC.IO.Exception (IOErrorType(..))
import GHC.IO.Exception (IOException(..))
import Data.Int (Int32)
import Foreign.Ptr (FunPtr)
import Foreign.Ptr (Ptr)
import GHC.Read (Read(readPrec))
import Data.Word (Word32)
import Data.Word (Word64)
import Text.Read.Lex (Lexeme(Ident))
import Data.ByteString (ByteString)
import Data.Kind (Type)
import Control.Monad.Trans.Cont (ContT(..))
import Data.Vector (Vector)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaCreateAllocator" ffiVmaCreateAllocator
:: Ptr AllocatorCreateInfo -> Ptr Allocator -> IO Result
createAllocator :: forall io
. (MonadIO io)
=>
AllocatorCreateInfo
-> io (Allocator)
createAllocator :: AllocatorCreateInfo -> io Allocator
createAllocator createInfo :: AllocatorCreateInfo
createInfo = IO Allocator -> io Allocator
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Allocator -> io Allocator)
-> (ContT Allocator IO Allocator -> IO Allocator)
-> ContT Allocator IO Allocator
-> io Allocator
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Allocator IO Allocator -> IO Allocator
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Allocator IO Allocator -> io Allocator)
-> ContT Allocator IO Allocator -> io Allocator
forall a b. (a -> b) -> a -> b
$ do
Ptr AllocatorCreateInfo
pCreateInfo <- ((Ptr AllocatorCreateInfo -> IO Allocator) -> IO Allocator)
-> ContT Allocator IO (Ptr AllocatorCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocatorCreateInfo -> IO Allocator) -> IO Allocator)
-> ContT Allocator IO (Ptr AllocatorCreateInfo))
-> ((Ptr AllocatorCreateInfo -> IO Allocator) -> IO Allocator)
-> ContT Allocator IO (Ptr AllocatorCreateInfo)
forall a b. (a -> b) -> a -> b
$ AllocatorCreateInfo
-> (Ptr AllocatorCreateInfo -> IO Allocator) -> IO Allocator
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocatorCreateInfo
createInfo)
Ptr Allocator
pPAllocator <- ((Ptr Allocator -> IO Allocator) -> IO Allocator)
-> ContT Allocator IO (Ptr Allocator)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocator -> IO Allocator) -> IO Allocator)
-> ContT Allocator IO (Ptr Allocator))
-> ((Ptr Allocator -> IO Allocator) -> IO Allocator)
-> ContT Allocator IO (Ptr Allocator)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Allocator)
-> (Ptr Allocator -> IO ())
-> (Ptr Allocator -> IO Allocator)
-> IO Allocator
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Allocator)
forall a. Int -> IO (Ptr a)
callocBytes @Allocator 8) Ptr Allocator -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT Allocator IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Allocator IO Result)
-> IO Result -> ContT Allocator IO Result
forall a b. (a -> b) -> a -> b
$ (Ptr AllocatorCreateInfo -> Ptr Allocator -> IO Result
ffiVmaCreateAllocator) Ptr AllocatorCreateInfo
pCreateInfo (Ptr Allocator
pPAllocator)
IO () -> ContT Allocator IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Allocator IO ()) -> IO () -> ContT Allocator 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))
Allocator
pAllocator <- IO Allocator -> ContT Allocator IO Allocator
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Allocator -> ContT Allocator IO Allocator)
-> IO Allocator -> ContT Allocator IO Allocator
forall a b. (a -> b) -> a -> b
$ Ptr Allocator -> IO Allocator
forall a. Storable a => Ptr a -> IO a
peek @Allocator Ptr Allocator
pPAllocator
Allocator -> ContT Allocator IO Allocator
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Allocator -> ContT Allocator IO Allocator)
-> Allocator -> ContT Allocator IO Allocator
forall a b. (a -> b) -> a -> b
$ (Allocator
pAllocator)
withAllocator :: forall io r . MonadIO io => AllocatorCreateInfo -> (io (Allocator) -> ((Allocator) -> io ()) -> r) -> r
withAllocator :: AllocatorCreateInfo
-> (io Allocator -> (Allocator -> io ()) -> r) -> r
withAllocator pCreateInfo :: AllocatorCreateInfo
pCreateInfo b :: io Allocator -> (Allocator -> io ()) -> r
b =
io Allocator -> (Allocator -> io ()) -> r
b (AllocatorCreateInfo -> io Allocator
forall (io :: * -> *).
MonadIO io =>
AllocatorCreateInfo -> io Allocator
createAllocator AllocatorCreateInfo
pCreateInfo)
(\(Allocator
o0) -> Allocator -> io ()
forall (io :: * -> *). MonadIO io => Allocator -> io ()
destroyAllocator Allocator
o0)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaDestroyAllocator" ffiVmaDestroyAllocator
:: Allocator -> IO ()
destroyAllocator :: forall io
. (MonadIO io)
=>
Allocator
-> io ()
destroyAllocator :: Allocator -> io ()
destroyAllocator allocator :: Allocator
allocator = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
(Allocator -> IO ()
ffiVmaDestroyAllocator) (Allocator
allocator)
() -> 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
"vmaGetAllocatorInfo" ffiVmaGetAllocatorInfo
:: Allocator -> Ptr AllocatorInfo -> IO ()
getAllocatorInfo :: forall io
. (MonadIO io)
=>
Allocator
-> io (AllocatorInfo)
getAllocatorInfo :: Allocator -> io AllocatorInfo
getAllocatorInfo allocator :: Allocator
allocator = IO AllocatorInfo -> io AllocatorInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AllocatorInfo -> io AllocatorInfo)
-> (ContT AllocatorInfo IO AllocatorInfo -> IO AllocatorInfo)
-> ContT AllocatorInfo IO AllocatorInfo
-> io AllocatorInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT AllocatorInfo IO AllocatorInfo -> IO AllocatorInfo
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT AllocatorInfo IO AllocatorInfo -> io AllocatorInfo)
-> ContT AllocatorInfo IO AllocatorInfo -> io AllocatorInfo
forall a b. (a -> b) -> a -> b
$ do
Ptr AllocatorInfo
pPAllocatorInfo <- ((Ptr AllocatorInfo -> IO AllocatorInfo) -> IO AllocatorInfo)
-> ContT AllocatorInfo IO (Ptr AllocatorInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct AllocatorInfo =>
(Ptr AllocatorInfo -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @AllocatorInfo)
IO () -> ContT AllocatorInfo IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT AllocatorInfo IO ())
-> IO () -> ContT AllocatorInfo IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Ptr AllocatorInfo -> IO ()
ffiVmaGetAllocatorInfo) (Allocator
allocator) (Ptr AllocatorInfo
pPAllocatorInfo)
AllocatorInfo
pAllocatorInfo <- IO AllocatorInfo -> ContT AllocatorInfo IO AllocatorInfo
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO AllocatorInfo -> ContT AllocatorInfo IO AllocatorInfo)
-> IO AllocatorInfo -> ContT AllocatorInfo IO AllocatorInfo
forall a b. (a -> b) -> a -> b
$ Ptr AllocatorInfo -> IO AllocatorInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AllocatorInfo Ptr AllocatorInfo
pPAllocatorInfo
AllocatorInfo -> ContT AllocatorInfo IO AllocatorInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AllocatorInfo -> ContT AllocatorInfo IO AllocatorInfo)
-> AllocatorInfo -> ContT AllocatorInfo IO AllocatorInfo
forall a b. (a -> b) -> a -> b
$ (AllocatorInfo
pAllocatorInfo)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaGetPhysicalDeviceProperties" ffiVmaGetPhysicalDeviceProperties
:: Allocator -> Ptr (Ptr PhysicalDeviceProperties) -> IO ()
getPhysicalDeviceProperties :: forall io
. (MonadIO io)
=>
Allocator
-> io (Ptr PhysicalDeviceProperties)
getPhysicalDeviceProperties :: Allocator -> io (Ptr PhysicalDeviceProperties)
getPhysicalDeviceProperties allocator :: Allocator
allocator = IO (Ptr PhysicalDeviceProperties)
-> io (Ptr PhysicalDeviceProperties)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr PhysicalDeviceProperties)
-> io (Ptr PhysicalDeviceProperties))
-> (ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties)
-> IO (Ptr PhysicalDeviceProperties))
-> ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties)
-> io (Ptr PhysicalDeviceProperties)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties)
-> IO (Ptr PhysicalDeviceProperties)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties)
-> io (Ptr PhysicalDeviceProperties))
-> ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties)
-> io (Ptr PhysicalDeviceProperties)
forall a b. (a -> b) -> a -> b
$ do
Ptr (Ptr PhysicalDeviceProperties)
pPpPhysicalDeviceProperties <- ((Ptr (Ptr PhysicalDeviceProperties)
-> IO (Ptr PhysicalDeviceProperties))
-> IO (Ptr PhysicalDeviceProperties))
-> ContT
(Ptr PhysicalDeviceProperties)
IO
(Ptr (Ptr PhysicalDeviceProperties))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Ptr PhysicalDeviceProperties)
-> IO (Ptr PhysicalDeviceProperties))
-> IO (Ptr PhysicalDeviceProperties))
-> ContT
(Ptr PhysicalDeviceProperties)
IO
(Ptr (Ptr PhysicalDeviceProperties)))
-> ((Ptr (Ptr PhysicalDeviceProperties)
-> IO (Ptr PhysicalDeviceProperties))
-> IO (Ptr PhysicalDeviceProperties))
-> ContT
(Ptr PhysicalDeviceProperties)
IO
(Ptr (Ptr PhysicalDeviceProperties))
forall a b. (a -> b) -> a -> b
$ IO (Ptr (Ptr PhysicalDeviceProperties))
-> (Ptr (Ptr PhysicalDeviceProperties) -> IO ())
-> (Ptr (Ptr PhysicalDeviceProperties)
-> IO (Ptr PhysicalDeviceProperties))
-> IO (Ptr PhysicalDeviceProperties)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr (Ptr PhysicalDeviceProperties))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr PhysicalDeviceProperties) 8) Ptr (Ptr PhysicalDeviceProperties) -> IO ()
forall a. Ptr a -> IO ()
free
IO () -> ContT (Ptr PhysicalDeviceProperties) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Ptr PhysicalDeviceProperties) IO ())
-> IO () -> ContT (Ptr PhysicalDeviceProperties) IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Ptr (Ptr PhysicalDeviceProperties) -> IO ()
ffiVmaGetPhysicalDeviceProperties) (Allocator
allocator) (Ptr (Ptr PhysicalDeviceProperties)
pPpPhysicalDeviceProperties)
Ptr PhysicalDeviceProperties
ppPhysicalDeviceProperties <- IO (Ptr PhysicalDeviceProperties)
-> ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (Ptr PhysicalDeviceProperties)
-> ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties))
-> IO (Ptr PhysicalDeviceProperties)
-> ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties)
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PhysicalDeviceProperties)
-> IO (Ptr PhysicalDeviceProperties)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PhysicalDeviceProperties) Ptr (Ptr PhysicalDeviceProperties)
pPpPhysicalDeviceProperties
Ptr PhysicalDeviceProperties
-> ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr PhysicalDeviceProperties
-> ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties))
-> Ptr PhysicalDeviceProperties
-> ContT
(Ptr PhysicalDeviceProperties) IO (Ptr PhysicalDeviceProperties)
forall a b. (a -> b) -> a -> b
$ (Ptr PhysicalDeviceProperties
ppPhysicalDeviceProperties)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaGetMemoryProperties" ffiVmaGetMemoryProperties
:: Allocator -> Ptr (Ptr PhysicalDeviceMemoryProperties) -> IO ()
getMemoryProperties :: forall io
. (MonadIO io)
=>
Allocator
-> io (Ptr PhysicalDeviceMemoryProperties)
getMemoryProperties :: Allocator -> io (Ptr PhysicalDeviceMemoryProperties)
getMemoryProperties allocator :: Allocator
allocator = IO (Ptr PhysicalDeviceMemoryProperties)
-> io (Ptr PhysicalDeviceMemoryProperties)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Ptr PhysicalDeviceMemoryProperties)
-> io (Ptr PhysicalDeviceMemoryProperties))
-> (ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties)
-> IO (Ptr PhysicalDeviceMemoryProperties))
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties)
-> io (Ptr PhysicalDeviceMemoryProperties)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties)
-> IO (Ptr PhysicalDeviceMemoryProperties)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties)
-> io (Ptr PhysicalDeviceMemoryProperties))
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties)
-> io (Ptr PhysicalDeviceMemoryProperties)
forall a b. (a -> b) -> a -> b
$ do
Ptr (Ptr PhysicalDeviceMemoryProperties)
pPpPhysicalDeviceMemoryProperties <- ((Ptr (Ptr PhysicalDeviceMemoryProperties)
-> IO (Ptr PhysicalDeviceMemoryProperties))
-> IO (Ptr PhysicalDeviceMemoryProperties))
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr (Ptr PhysicalDeviceMemoryProperties))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (Ptr PhysicalDeviceMemoryProperties)
-> IO (Ptr PhysicalDeviceMemoryProperties))
-> IO (Ptr PhysicalDeviceMemoryProperties))
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr (Ptr PhysicalDeviceMemoryProperties)))
-> ((Ptr (Ptr PhysicalDeviceMemoryProperties)
-> IO (Ptr PhysicalDeviceMemoryProperties))
-> IO (Ptr PhysicalDeviceMemoryProperties))
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr (Ptr PhysicalDeviceMemoryProperties))
forall a b. (a -> b) -> a -> b
$ IO (Ptr (Ptr PhysicalDeviceMemoryProperties))
-> (Ptr (Ptr PhysicalDeviceMemoryProperties) -> IO ())
-> (Ptr (Ptr PhysicalDeviceMemoryProperties)
-> IO (Ptr PhysicalDeviceMemoryProperties))
-> IO (Ptr PhysicalDeviceMemoryProperties)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr (Ptr PhysicalDeviceMemoryProperties))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr PhysicalDeviceMemoryProperties) 8) Ptr (Ptr PhysicalDeviceMemoryProperties) -> IO ()
forall a. Ptr a -> IO ()
free
IO () -> ContT (Ptr PhysicalDeviceMemoryProperties) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Ptr PhysicalDeviceMemoryProperties) IO ())
-> IO () -> ContT (Ptr PhysicalDeviceMemoryProperties) IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Ptr (Ptr PhysicalDeviceMemoryProperties) -> IO ()
ffiVmaGetMemoryProperties) (Allocator
allocator) (Ptr (Ptr PhysicalDeviceMemoryProperties)
pPpPhysicalDeviceMemoryProperties)
Ptr PhysicalDeviceMemoryProperties
ppPhysicalDeviceMemoryProperties <- IO (Ptr PhysicalDeviceMemoryProperties)
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO (Ptr PhysicalDeviceMemoryProperties)
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties))
-> IO (Ptr PhysicalDeviceMemoryProperties)
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties)
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PhysicalDeviceMemoryProperties)
-> IO (Ptr PhysicalDeviceMemoryProperties)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PhysicalDeviceMemoryProperties) Ptr (Ptr PhysicalDeviceMemoryProperties)
pPpPhysicalDeviceMemoryProperties
Ptr PhysicalDeviceMemoryProperties
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr PhysicalDeviceMemoryProperties
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties))
-> Ptr PhysicalDeviceMemoryProperties
-> ContT
(Ptr PhysicalDeviceMemoryProperties)
IO
(Ptr PhysicalDeviceMemoryProperties)
forall a b. (a -> b) -> a -> b
$ (Ptr PhysicalDeviceMemoryProperties
ppPhysicalDeviceMemoryProperties)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaGetMemoryTypeProperties" ffiVmaGetMemoryTypeProperties
:: Allocator -> Word32 -> Ptr MemoryPropertyFlags -> IO ()
getMemoryTypeProperties :: forall io
. (MonadIO io)
=>
Allocator
->
("memoryTypeIndex" ::: Word32)
-> io (MemoryPropertyFlags)
getMemoryTypeProperties :: Allocator
-> ("memoryTypeIndex" ::: Word32) -> io MemoryPropertyFlags
getMemoryTypeProperties allocator :: Allocator
allocator memoryTypeIndex :: "memoryTypeIndex" ::: Word32
memoryTypeIndex = IO MemoryPropertyFlags -> io MemoryPropertyFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO MemoryPropertyFlags -> io MemoryPropertyFlags)
-> (ContT MemoryPropertyFlags IO MemoryPropertyFlags
-> IO MemoryPropertyFlags)
-> ContT MemoryPropertyFlags IO MemoryPropertyFlags
-> io MemoryPropertyFlags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT MemoryPropertyFlags IO MemoryPropertyFlags
-> IO MemoryPropertyFlags
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT MemoryPropertyFlags IO MemoryPropertyFlags
-> io MemoryPropertyFlags)
-> ContT MemoryPropertyFlags IO MemoryPropertyFlags
-> io MemoryPropertyFlags
forall a b. (a -> b) -> a -> b
$ do
Ptr MemoryPropertyFlags
pPFlags <- ((Ptr MemoryPropertyFlags -> IO MemoryPropertyFlags)
-> IO MemoryPropertyFlags)
-> ContT MemoryPropertyFlags IO (Ptr MemoryPropertyFlags)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr MemoryPropertyFlags -> IO MemoryPropertyFlags)
-> IO MemoryPropertyFlags)
-> ContT MemoryPropertyFlags IO (Ptr MemoryPropertyFlags))
-> ((Ptr MemoryPropertyFlags -> IO MemoryPropertyFlags)
-> IO MemoryPropertyFlags)
-> ContT MemoryPropertyFlags IO (Ptr MemoryPropertyFlags)
forall a b. (a -> b) -> a -> b
$ IO (Ptr MemoryPropertyFlags)
-> (Ptr MemoryPropertyFlags -> IO ())
-> (Ptr MemoryPropertyFlags -> IO MemoryPropertyFlags)
-> IO MemoryPropertyFlags
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr MemoryPropertyFlags)
forall a. Int -> IO (Ptr a)
callocBytes @MemoryPropertyFlags 4) Ptr MemoryPropertyFlags -> IO ()
forall a. Ptr a -> IO ()
free
IO () -> ContT MemoryPropertyFlags IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT MemoryPropertyFlags IO ())
-> IO () -> ContT MemoryPropertyFlags IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator
-> ("memoryTypeIndex" ::: Word32)
-> Ptr MemoryPropertyFlags
-> IO ()
ffiVmaGetMemoryTypeProperties) (Allocator
allocator) ("memoryTypeIndex" ::: Word32
memoryTypeIndex) (Ptr MemoryPropertyFlags
pPFlags)
MemoryPropertyFlags
pFlags <- IO MemoryPropertyFlags
-> ContT MemoryPropertyFlags IO MemoryPropertyFlags
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO MemoryPropertyFlags
-> ContT MemoryPropertyFlags IO MemoryPropertyFlags)
-> IO MemoryPropertyFlags
-> ContT MemoryPropertyFlags IO MemoryPropertyFlags
forall a b. (a -> b) -> a -> b
$ Ptr MemoryPropertyFlags -> IO MemoryPropertyFlags
forall a. Storable a => Ptr a -> IO a
peek @MemoryPropertyFlags Ptr MemoryPropertyFlags
pPFlags
MemoryPropertyFlags
-> ContT MemoryPropertyFlags IO MemoryPropertyFlags
forall (f :: * -> *) a. Applicative f => a -> f a
pure (MemoryPropertyFlags
-> ContT MemoryPropertyFlags IO MemoryPropertyFlags)
-> MemoryPropertyFlags
-> ContT MemoryPropertyFlags IO MemoryPropertyFlags
forall a b. (a -> b) -> a -> b
$ (MemoryPropertyFlags
pFlags)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaSetCurrentFrameIndex" ffiVmaSetCurrentFrameIndex
:: Allocator -> Word32 -> IO ()
setCurrentFrameIndex :: forall io
. (MonadIO io)
=>
Allocator
->
("frameIndex" ::: Word32)
-> io ()
setCurrentFrameIndex :: Allocator -> ("memoryTypeIndex" ::: Word32) -> io ()
setCurrentFrameIndex allocator :: Allocator
allocator frameIndex :: "memoryTypeIndex" ::: Word32
frameIndex = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
(Allocator -> ("memoryTypeIndex" ::: Word32) -> IO ()
ffiVmaSetCurrentFrameIndex) (Allocator
allocator) ("memoryTypeIndex" ::: Word32
frameIndex)
() -> 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
"vmaCalculateStats" ffiVmaCalculateStats
:: Allocator -> Ptr Stats -> IO ()
calculateStats :: forall io
. (MonadIO io)
=>
Allocator
-> io (Stats)
calculateStats :: Allocator -> io Stats
calculateStats allocator :: Allocator
allocator = IO Stats -> io Stats
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Stats -> io Stats)
-> (ContT Stats IO Stats -> IO Stats)
-> ContT Stats IO Stats
-> io Stats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Stats IO Stats -> IO Stats
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Stats IO Stats -> io Stats)
-> ContT Stats IO Stats -> io Stats
forall a b. (a -> b) -> a -> b
$ do
Ptr Stats
pPStats <- ((Ptr Stats -> IO Stats) -> IO Stats) -> ContT Stats IO (Ptr Stats)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b. ToCStruct Stats => (Ptr Stats -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @Stats)
IO () -> ContT Stats IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Stats IO ()) -> IO () -> ContT Stats IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Ptr Stats -> IO ()
ffiVmaCalculateStats) (Allocator
allocator) (Ptr Stats
pPStats)
Stats
pStats <- IO Stats -> ContT Stats IO Stats
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Stats -> ContT Stats IO Stats)
-> IO Stats -> ContT Stats IO Stats
forall a b. (a -> b) -> a -> b
$ Ptr Stats -> IO Stats
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Stats Ptr Stats
pPStats
Stats -> ContT Stats IO Stats
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Stats -> ContT Stats IO Stats) -> Stats -> ContT Stats IO Stats
forall a b. (a -> b) -> a -> b
$ (Stats
pStats)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaGetBudget" ffiVmaGetBudget
:: Allocator -> Ptr Budget -> IO ()
getBudget :: forall io
. (MonadIO io)
=>
Allocator
-> io (Budget)
getBudget :: Allocator -> io Budget
getBudget allocator :: Allocator
allocator = IO Budget -> io Budget
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Budget -> io Budget)
-> (ContT Budget IO Budget -> IO Budget)
-> ContT Budget IO Budget
-> io Budget
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Budget IO Budget -> IO Budget
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Budget IO Budget -> io Budget)
-> ContT Budget IO Budget -> io Budget
forall a b. (a -> b) -> a -> b
$ do
Ptr Budget
pPBudget <- ((Ptr Budget -> IO Budget) -> IO Budget)
-> ContT Budget IO (Ptr Budget)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b. ToCStruct Budget => (Ptr Budget -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @Budget)
IO () -> ContT Budget IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Budget IO ()) -> IO () -> ContT Budget IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Ptr Budget -> IO ()
ffiVmaGetBudget) (Allocator
allocator) (Ptr Budget
pPBudget)
Budget
pBudget <- IO Budget -> ContT Budget IO Budget
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Budget -> ContT Budget IO Budget)
-> IO Budget -> ContT Budget IO Budget
forall a b. (a -> b) -> a -> b
$ Ptr Budget -> IO Budget
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @Budget Ptr Budget
pPBudget
Budget -> ContT Budget IO Budget
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Budget -> ContT Budget IO Budget)
-> Budget -> ContT Budget IO Budget
forall a b. (a -> b) -> a -> b
$ (Budget
pBudget)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaBuildStatsString" ffiVmaBuildStatsString
:: Allocator -> Ptr (Ptr CChar) -> Bool32 -> IO ()
buildStatsString :: forall io
. (MonadIO io)
=>
Allocator
->
("detailedMap" ::: Bool)
-> io (("statsString" ::: Ptr CChar))
buildStatsString :: Allocator -> Bool -> io ("statsString" ::: Ptr CChar)
buildStatsString allocator :: Allocator
allocator detailedMap :: Bool
detailedMap = IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar))
-> (ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ do
Ptr ("statsString" ::: Ptr CChar)
pPpStatsString <- ((Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar)
IO
(Ptr ("statsString" ::: Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar)
IO
(Ptr ("statsString" ::: Ptr CChar)))
-> ((Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar)
IO
(Ptr ("statsString" ::: Ptr CChar))
forall a b. (a -> b) -> a -> b
$ IO (Ptr ("statsString" ::: Ptr CChar))
-> (Ptr ("statsString" ::: Ptr CChar) -> IO ())
-> (Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr ("statsString" ::: Ptr CChar))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr CChar) 8) Ptr ("statsString" ::: Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
free
IO () -> ContT ("statsString" ::: Ptr CChar) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("statsString" ::: Ptr CChar) IO ())
-> IO () -> ContT ("statsString" ::: Ptr CChar) IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Ptr ("statsString" ::: Ptr CChar) -> Bool32 -> IO ()
ffiVmaBuildStatsString) (Allocator
allocator) (Ptr ("statsString" ::: Ptr CChar)
pPpStatsString) (Bool -> Bool32
boolToBool32 (Bool
detailedMap))
"statsString" ::: Ptr CChar
ppStatsString <- IO ("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr CChar) Ptr ("statsString" ::: Ptr CChar)
pPpStatsString
("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar))
-> ("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("statsString" ::: Ptr CChar
ppStatsString)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaFreeStatsString" ffiVmaFreeStatsString
:: Allocator -> Ptr CChar -> IO ()
freeStatsString :: forall io
. (MonadIO io)
=>
Allocator
->
("statsString" ::: Ptr CChar)
-> io ()
freeStatsString :: Allocator -> ("statsString" ::: Ptr CChar) -> io ()
freeStatsString allocator :: Allocator
allocator statsString :: "statsString" ::: Ptr CChar
statsString = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
(Allocator -> ("statsString" ::: Ptr CChar) -> IO ()
ffiVmaFreeStatsString) (Allocator
allocator) ("statsString" ::: Ptr CChar
statsString)
() -> 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
"vmaFindMemoryTypeIndex" ffiVmaFindMemoryTypeIndex
:: Allocator -> Word32 -> Ptr AllocationCreateInfo -> Ptr Word32 -> IO Result
findMemoryTypeIndex :: forall io
. (MonadIO io)
=>
Allocator
->
("memoryTypeBits" ::: Word32)
->
AllocationCreateInfo
-> io (("memoryTypeIndex" ::: Word32))
findMemoryTypeIndex :: Allocator
-> ("memoryTypeIndex" ::: Word32)
-> AllocationCreateInfo
-> io ("memoryTypeIndex" ::: Word32)
findMemoryTypeIndex allocator :: Allocator
allocator memoryTypeBits :: "memoryTypeIndex" ::: Word32
memoryTypeBits allocationCreateInfo :: AllocationCreateInfo
allocationCreateInfo = IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32))
-> (ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32)
forall a b. (a -> b) -> a -> b
$ do
Ptr AllocationCreateInfo
pAllocationCreateInfo <- ((Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr AllocationCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr AllocationCreateInfo))
-> ((Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr AllocationCreateInfo)
forall a b. (a -> b) -> a -> b
$ AllocationCreateInfo
-> (Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCreateInfo
allocationCreateInfo)
Ptr ("memoryTypeIndex" ::: Word32)
pPMemoryTypeIndex <- ((Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32)
IO
(Ptr ("memoryTypeIndex" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32)
IO
(Ptr ("memoryTypeIndex" ::: Word32)))
-> ((Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32)
IO
(Ptr ("memoryTypeIndex" ::: Word32))
forall a b. (a -> b) -> a -> b
$ IO (Ptr ("memoryTypeIndex" ::: Word32))
-> (Ptr ("memoryTypeIndex" ::: Word32) -> IO ())
-> (Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr ("memoryTypeIndex" ::: Word32))
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) Ptr ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT ("memoryTypeIndex" ::: Word32) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT ("memoryTypeIndex" ::: Word32) IO Result)
-> IO Result -> ContT ("memoryTypeIndex" ::: Word32) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> ("memoryTypeIndex" ::: Word32)
-> Ptr AllocationCreateInfo
-> Ptr ("memoryTypeIndex" ::: Word32)
-> IO Result
ffiVmaFindMemoryTypeIndex) (Allocator
allocator) ("memoryTypeIndex" ::: Word32
memoryTypeBits) Ptr AllocationCreateInfo
pAllocationCreateInfo (Ptr ("memoryTypeIndex" ::: Word32)
pPMemoryTypeIndex)
IO () -> ContT ("memoryTypeIndex" ::: Word32) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("memoryTypeIndex" ::: Word32) IO ())
-> IO () -> ContT ("memoryTypeIndex" ::: Word32) 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))
"memoryTypeIndex" ::: Word32
pMemoryTypeIndex <- IO ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall a b. (a -> b) -> a -> b
$ Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 Ptr ("memoryTypeIndex" ::: Word32)
pPMemoryTypeIndex
("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32))
-> ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall a b. (a -> b) -> a -> b
$ ("memoryTypeIndex" ::: Word32
pMemoryTypeIndex)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaFindMemoryTypeIndexForBufferInfo" ffiVmaFindMemoryTypeIndexForBufferInfo
:: Allocator -> Ptr (SomeStruct BufferCreateInfo) -> Ptr AllocationCreateInfo -> Ptr Word32 -> IO Result
findMemoryTypeIndexForBufferInfo :: forall a io
. (Extendss BufferCreateInfo a, PokeChain a, MonadIO io)
=>
Allocator
->
(BufferCreateInfo a)
->
AllocationCreateInfo
-> io (("memoryTypeIndex" ::: Word32))
findMemoryTypeIndexForBufferInfo :: Allocator
-> BufferCreateInfo a
-> AllocationCreateInfo
-> io ("memoryTypeIndex" ::: Word32)
findMemoryTypeIndexForBufferInfo allocator :: Allocator
allocator bufferCreateInfo :: BufferCreateInfo a
bufferCreateInfo allocationCreateInfo :: AllocationCreateInfo
allocationCreateInfo = IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32))
-> (ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32)
forall a b. (a -> b) -> a -> b
$ do
Ptr (BufferCreateInfo a)
pBufferCreateInfo <- ((Ptr (BufferCreateInfo a) -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr (BufferCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (BufferCreateInfo a) -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr (BufferCreateInfo a)))
-> ((Ptr (BufferCreateInfo a) -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr (BufferCreateInfo a))
forall a b. (a -> b) -> a -> b
$ BufferCreateInfo a
-> (Ptr (BufferCreateInfo a) -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (BufferCreateInfo a
bufferCreateInfo)
Ptr AllocationCreateInfo
pAllocationCreateInfo <- ((Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr AllocationCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr AllocationCreateInfo))
-> ((Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr AllocationCreateInfo)
forall a b. (a -> b) -> a -> b
$ AllocationCreateInfo
-> (Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCreateInfo
allocationCreateInfo)
Ptr ("memoryTypeIndex" ::: Word32)
pPMemoryTypeIndex <- ((Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32)
IO
(Ptr ("memoryTypeIndex" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32)
IO
(Ptr ("memoryTypeIndex" ::: Word32)))
-> ((Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32)
IO
(Ptr ("memoryTypeIndex" ::: Word32))
forall a b. (a -> b) -> a -> b
$ IO (Ptr ("memoryTypeIndex" ::: Word32))
-> (Ptr ("memoryTypeIndex" ::: Word32) -> IO ())
-> (Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr ("memoryTypeIndex" ::: Word32))
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) Ptr ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT ("memoryTypeIndex" ::: Word32) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT ("memoryTypeIndex" ::: Word32) IO Result)
-> IO Result -> ContT ("memoryTypeIndex" ::: Word32) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Ptr (SomeStruct BufferCreateInfo)
-> Ptr AllocationCreateInfo
-> Ptr ("memoryTypeIndex" ::: Word32)
-> IO Result
ffiVmaFindMemoryTypeIndexForBufferInfo) (Allocator
allocator) (Ptr (BufferCreateInfo a) -> Ptr (SomeStruct BufferCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (BufferCreateInfo a)
pBufferCreateInfo) Ptr AllocationCreateInfo
pAllocationCreateInfo (Ptr ("memoryTypeIndex" ::: Word32)
pPMemoryTypeIndex)
IO () -> ContT ("memoryTypeIndex" ::: Word32) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("memoryTypeIndex" ::: Word32) IO ())
-> IO () -> ContT ("memoryTypeIndex" ::: Word32) 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))
"memoryTypeIndex" ::: Word32
pMemoryTypeIndex <- IO ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall a b. (a -> b) -> a -> b
$ Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 Ptr ("memoryTypeIndex" ::: Word32)
pPMemoryTypeIndex
("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32))
-> ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall a b. (a -> b) -> a -> b
$ ("memoryTypeIndex" ::: Word32
pMemoryTypeIndex)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaFindMemoryTypeIndexForImageInfo" ffiVmaFindMemoryTypeIndexForImageInfo
:: Allocator -> Ptr (SomeStruct ImageCreateInfo) -> Ptr AllocationCreateInfo -> Ptr Word32 -> IO Result
findMemoryTypeIndexForImageInfo :: forall a io
. (Extendss ImageCreateInfo a, PokeChain a, MonadIO io)
=>
Allocator
->
(ImageCreateInfo a)
->
AllocationCreateInfo
-> io (("memoryTypeIndex" ::: Word32))
findMemoryTypeIndexForImageInfo :: Allocator
-> ImageCreateInfo a
-> AllocationCreateInfo
-> io ("memoryTypeIndex" ::: Word32)
findMemoryTypeIndexForImageInfo allocator :: Allocator
allocator imageCreateInfo :: ImageCreateInfo a
imageCreateInfo allocationCreateInfo :: AllocationCreateInfo
allocationCreateInfo = IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32))
-> (ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
-> io ("memoryTypeIndex" ::: Word32)
forall a b. (a -> b) -> a -> b
$ do
Ptr (ImageCreateInfo a)
pImageCreateInfo <- ((Ptr (ImageCreateInfo a) -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr (ImageCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (ImageCreateInfo a) -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr (ImageCreateInfo a)))
-> ((Ptr (ImageCreateInfo a) -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr (ImageCreateInfo a))
forall a b. (a -> b) -> a -> b
$ ImageCreateInfo a
-> (Ptr (ImageCreateInfo a) -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ImageCreateInfo a
imageCreateInfo)
Ptr AllocationCreateInfo
pAllocationCreateInfo <- ((Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr AllocationCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr AllocationCreateInfo))
-> ((Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32) IO (Ptr AllocationCreateInfo)
forall a b. (a -> b) -> a -> b
$ AllocationCreateInfo
-> (Ptr AllocationCreateInfo -> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCreateInfo
allocationCreateInfo)
Ptr ("memoryTypeIndex" ::: Word32)
pPMemoryTypeIndex <- ((Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32)
IO
(Ptr ("memoryTypeIndex" ::: Word32))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32)
IO
(Ptr ("memoryTypeIndex" ::: Word32)))
-> ((Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32))
-> ContT
("memoryTypeIndex" ::: Word32)
IO
(Ptr ("memoryTypeIndex" ::: Word32))
forall a b. (a -> b) -> a -> b
$ IO (Ptr ("memoryTypeIndex" ::: Word32))
-> (Ptr ("memoryTypeIndex" ::: Word32) -> IO ())
-> (Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr ("memoryTypeIndex" ::: Word32))
forall a. Int -> IO (Ptr a)
callocBytes @Word32 4) Ptr ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT ("memoryTypeIndex" ::: Word32) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT ("memoryTypeIndex" ::: Word32) IO Result)
-> IO Result -> ContT ("memoryTypeIndex" ::: Word32) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Ptr (SomeStruct ImageCreateInfo)
-> Ptr AllocationCreateInfo
-> Ptr ("memoryTypeIndex" ::: Word32)
-> IO Result
ffiVmaFindMemoryTypeIndexForImageInfo) (Allocator
allocator) (Ptr (ImageCreateInfo a) -> Ptr (SomeStruct ImageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (ImageCreateInfo a)
pImageCreateInfo) Ptr AllocationCreateInfo
pAllocationCreateInfo (Ptr ("memoryTypeIndex" ::: Word32)
pPMemoryTypeIndex)
IO () -> ContT ("memoryTypeIndex" ::: Word32) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("memoryTypeIndex" ::: Word32) IO ())
-> IO () -> ContT ("memoryTypeIndex" ::: Word32) 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))
"memoryTypeIndex" ::: Word32
pMemoryTypeIndex <- IO ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32))
-> IO ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall a b. (a -> b) -> a -> b
$ Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 Ptr ("memoryTypeIndex" ::: Word32)
pPMemoryTypeIndex
("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32))
-> ("memoryTypeIndex" ::: Word32)
-> ContT
("memoryTypeIndex" ::: Word32) IO ("memoryTypeIndex" ::: Word32)
forall a b. (a -> b) -> a -> b
$ ("memoryTypeIndex" ::: Word32
pMemoryTypeIndex)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaCreatePool" ffiVmaCreatePool
:: Allocator -> Ptr PoolCreateInfo -> Ptr Pool -> IO Result
createPool :: forall io
. (MonadIO io)
=>
Allocator
->
PoolCreateInfo
-> io (Pool)
createPool :: Allocator -> PoolCreateInfo -> io Pool
createPool allocator :: Allocator
allocator createInfo :: PoolCreateInfo
createInfo = IO Pool -> io Pool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Pool -> io Pool)
-> (ContT Pool IO Pool -> IO Pool) -> ContT Pool IO Pool -> io Pool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Pool IO Pool -> IO Pool
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Pool IO Pool -> io Pool) -> ContT Pool IO Pool -> io Pool
forall a b. (a -> b) -> a -> b
$ do
Ptr PoolCreateInfo
pCreateInfo <- ((Ptr PoolCreateInfo -> IO Pool) -> IO Pool)
-> ContT Pool IO (Ptr PoolCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr PoolCreateInfo -> IO Pool) -> IO Pool)
-> ContT Pool IO (Ptr PoolCreateInfo))
-> ((Ptr PoolCreateInfo -> IO Pool) -> IO Pool)
-> ContT Pool IO (Ptr PoolCreateInfo)
forall a b. (a -> b) -> a -> b
$ PoolCreateInfo -> (Ptr PoolCreateInfo -> IO Pool) -> IO Pool
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (PoolCreateInfo
createInfo)
Ptr Pool
pPPool <- ((Ptr Pool -> IO Pool) -> IO Pool) -> ContT Pool IO (Ptr Pool)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Pool -> IO Pool) -> IO Pool) -> ContT Pool IO (Ptr Pool))
-> ((Ptr Pool -> IO Pool) -> IO Pool) -> ContT Pool IO (Ptr Pool)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Pool)
-> (Ptr Pool -> IO ()) -> (Ptr Pool -> IO Pool) -> IO Pool
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Pool)
forall a. Int -> IO (Ptr a)
callocBytes @Pool 8) Ptr Pool -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT Pool IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT Pool IO Result)
-> IO Result -> ContT Pool IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator -> Ptr PoolCreateInfo -> Ptr Pool -> IO Result
ffiVmaCreatePool) (Allocator
allocator) Ptr PoolCreateInfo
pCreateInfo (Ptr Pool
pPPool)
IO () -> ContT Pool IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Pool IO ()) -> IO () -> ContT Pool 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))
Pool
pPool <- IO Pool -> ContT Pool IO Pool
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Pool -> ContT Pool IO Pool) -> IO Pool -> ContT Pool IO Pool
forall a b. (a -> b) -> a -> b
$ Ptr Pool -> IO Pool
forall a. Storable a => Ptr a -> IO a
peek @Pool Ptr Pool
pPPool
Pool -> ContT Pool IO Pool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Pool -> ContT Pool IO Pool) -> Pool -> ContT Pool IO Pool
forall a b. (a -> b) -> a -> b
$ (Pool
pPool)
withPool :: forall io r . MonadIO io => Allocator -> PoolCreateInfo -> (io (Pool) -> ((Pool) -> io ()) -> r) -> r
withPool :: Allocator
-> PoolCreateInfo -> (io Pool -> (Pool -> io ()) -> r) -> r
withPool allocator :: Allocator
allocator pCreateInfo :: PoolCreateInfo
pCreateInfo b :: io Pool -> (Pool -> io ()) -> r
b =
io Pool -> (Pool -> io ()) -> r
b (Allocator -> PoolCreateInfo -> io Pool
forall (io :: * -> *).
MonadIO io =>
Allocator -> PoolCreateInfo -> io Pool
createPool Allocator
allocator PoolCreateInfo
pCreateInfo)
(\(Pool
o0) -> Allocator -> Pool -> io ()
forall (io :: * -> *). MonadIO io => Allocator -> Pool -> io ()
destroyPool Allocator
allocator Pool
o0)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaDestroyPool" ffiVmaDestroyPool
:: Allocator -> Pool -> IO ()
destroyPool :: forall io
. (MonadIO io)
=>
Allocator
->
Pool
-> io ()
destroyPool :: Allocator -> Pool -> io ()
destroyPool allocator :: Allocator
allocator pool :: Pool
pool = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
(Allocator -> Pool -> IO ()
ffiVmaDestroyPool) (Allocator
allocator) (Pool
pool)
() -> 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
"vmaGetPoolStats" ffiVmaGetPoolStats
:: Allocator -> Pool -> Ptr PoolStats -> IO ()
getPoolStats :: forall io
. (MonadIO io)
=>
Allocator
->
Pool
-> io (PoolStats)
getPoolStats :: Allocator -> Pool -> io PoolStats
getPoolStats allocator :: Allocator
allocator pool :: Pool
pool = IO PoolStats -> io PoolStats
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PoolStats -> io PoolStats)
-> (ContT PoolStats IO PoolStats -> IO PoolStats)
-> ContT PoolStats IO PoolStats
-> io PoolStats
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT PoolStats IO PoolStats -> IO PoolStats
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT PoolStats IO PoolStats -> io PoolStats)
-> ContT PoolStats IO PoolStats -> io PoolStats
forall a b. (a -> b) -> a -> b
$ do
Ptr PoolStats
pPPoolStats <- ((Ptr PoolStats -> IO PoolStats) -> IO PoolStats)
-> ContT PoolStats IO (Ptr PoolStats)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b. ToCStruct PoolStats => (Ptr PoolStats -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @PoolStats)
IO () -> ContT PoolStats IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT PoolStats IO ()) -> IO () -> ContT PoolStats IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Pool -> Ptr PoolStats -> IO ()
ffiVmaGetPoolStats) (Allocator
allocator) (Pool
pool) (Ptr PoolStats
pPPoolStats)
PoolStats
pPoolStats <- IO PoolStats -> ContT PoolStats IO PoolStats
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO PoolStats -> ContT PoolStats IO PoolStats)
-> IO PoolStats -> ContT PoolStats IO PoolStats
forall a b. (a -> b) -> a -> b
$ Ptr PoolStats -> IO PoolStats
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @PoolStats Ptr PoolStats
pPPoolStats
PoolStats -> ContT PoolStats IO PoolStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PoolStats -> ContT PoolStats IO PoolStats)
-> PoolStats -> ContT PoolStats IO PoolStats
forall a b. (a -> b) -> a -> b
$ (PoolStats
pPoolStats)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaMakePoolAllocationsLost" ffiVmaMakePoolAllocationsLost
:: Allocator -> Pool -> Ptr CSize -> IO ()
makePoolAllocationsLost :: forall io
. (MonadIO io)
=>
Allocator
->
Pool
-> io (("lostAllocationCount" ::: Word64))
makePoolAllocationsLost :: Allocator -> Pool -> io ("lostAllocationCount" ::: Word64)
makePoolAllocationsLost allocator :: Allocator
allocator pool :: Pool
pool = IO ("lostAllocationCount" ::: Word64)
-> io ("lostAllocationCount" ::: Word64)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("lostAllocationCount" ::: Word64)
-> io ("lostAllocationCount" ::: Word64))
-> (ContT
("lostAllocationCount" ::: Word64)
IO
("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64))
-> ContT
("lostAllocationCount" ::: Word64)
IO
("lostAllocationCount" ::: Word64)
-> io ("lostAllocationCount" ::: Word64)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("lostAllocationCount" ::: Word64)
IO
("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("lostAllocationCount" ::: Word64)
IO
("lostAllocationCount" ::: Word64)
-> io ("lostAllocationCount" ::: Word64))
-> ContT
("lostAllocationCount" ::: Word64)
IO
("lostAllocationCount" ::: Word64)
-> io ("lostAllocationCount" ::: Word64)
forall a b. (a -> b) -> a -> b
$ do
Ptr CSize
pPLostAllocationCount <- ((Ptr CSize -> IO ("lostAllocationCount" ::: Word64))
-> IO ("lostAllocationCount" ::: Word64))
-> ContT ("lostAllocationCount" ::: Word64) IO (Ptr CSize)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr CSize -> IO ("lostAllocationCount" ::: Word64))
-> IO ("lostAllocationCount" ::: Word64))
-> ContT ("lostAllocationCount" ::: Word64) IO (Ptr CSize))
-> ((Ptr CSize -> IO ("lostAllocationCount" ::: Word64))
-> IO ("lostAllocationCount" ::: Word64))
-> ContT ("lostAllocationCount" ::: Word64) IO (Ptr CSize)
forall a b. (a -> b) -> a -> b
$ IO (Ptr CSize)
-> (Ptr CSize -> IO ())
-> (Ptr CSize -> IO ("lostAllocationCount" ::: Word64))
-> IO ("lostAllocationCount" ::: Word64)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr CSize)
forall a. Int -> IO (Ptr a)
callocBytes @CSize 8) Ptr CSize -> IO ()
forall a. Ptr a -> IO ()
free
IO () -> ContT ("lostAllocationCount" ::: Word64) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("lostAllocationCount" ::: Word64) IO ())
-> IO () -> ContT ("lostAllocationCount" ::: Word64) IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Pool -> Ptr CSize -> IO ()
ffiVmaMakePoolAllocationsLost) (Allocator
allocator) (Pool
pool) (Ptr CSize
pPLostAllocationCount)
CSize
pLostAllocationCount <- IO CSize -> ContT ("lostAllocationCount" ::: Word64) IO CSize
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO CSize -> ContT ("lostAllocationCount" ::: Word64) IO CSize)
-> IO CSize -> ContT ("lostAllocationCount" ::: Word64) IO CSize
forall a b. (a -> b) -> a -> b
$ Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize Ptr CSize
pPLostAllocationCount
("lostAllocationCount" ::: Word64)
-> ContT
("lostAllocationCount" ::: Word64)
IO
("lostAllocationCount" ::: Word64)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("lostAllocationCount" ::: Word64)
-> ContT
("lostAllocationCount" ::: Word64)
IO
("lostAllocationCount" ::: Word64))
-> ("lostAllocationCount" ::: Word64)
-> ContT
("lostAllocationCount" ::: Word64)
IO
("lostAllocationCount" ::: Word64)
forall a b. (a -> b) -> a -> b
$ (((\(CSize a :: "lostAllocationCount" ::: Word64
a) -> "lostAllocationCount" ::: Word64
a) CSize
pLostAllocationCount))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaCheckPoolCorruption" ffiVmaCheckPoolCorruption
:: Allocator -> Pool -> IO Result
checkPoolCorruption :: forall io
. (MonadIO io)
=>
Allocator
->
Pool
-> io ()
checkPoolCorruption :: Allocator -> Pool -> io ()
checkPoolCorruption allocator :: Allocator
allocator pool :: Pool
pool = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator -> Pool -> IO Result
ffiVmaCheckPoolCorruption) (Allocator
allocator) (Pool
pool)
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
"vmaGetPoolName" ffiVmaGetPoolName
:: Allocator -> Pool -> Ptr (Ptr CChar) -> IO ()
getPoolName :: forall io
. (MonadIO io)
=>
Allocator
->
Pool
-> io (("name" ::: Ptr CChar))
getPoolName :: Allocator -> Pool -> io ("statsString" ::: Ptr CChar)
getPoolName allocator :: Allocator
allocator pool :: Pool
pool = IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar))
-> (ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
-> io ("statsString" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ do
Ptr ("statsString" ::: Ptr CChar)
pPpName <- ((Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar)
IO
(Ptr ("statsString" ::: Ptr CChar))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar)
IO
(Ptr ("statsString" ::: Ptr CChar)))
-> ((Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar))
-> ContT
("statsString" ::: Ptr CChar)
IO
(Ptr ("statsString" ::: Ptr CChar))
forall a b. (a -> b) -> a -> b
$ IO (Ptr ("statsString" ::: Ptr CChar))
-> (Ptr ("statsString" ::: Ptr CChar) -> IO ())
-> (Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr ("statsString" ::: Ptr CChar))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr CChar) 8) Ptr ("statsString" ::: Ptr CChar) -> IO ()
forall a. Ptr a -> IO ()
free
IO () -> ContT ("statsString" ::: Ptr CChar) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("statsString" ::: Ptr CChar) IO ())
-> IO () -> ContT ("statsString" ::: Ptr CChar) IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Pool -> Ptr ("statsString" ::: Ptr CChar) -> IO ()
ffiVmaGetPoolName) (Allocator
allocator) (Pool
pool) (Ptr ("statsString" ::: Ptr CChar)
pPpName)
"statsString" ::: Ptr CChar
ppName <- IO ("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar))
-> IO ("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr CChar) Ptr ("statsString" ::: Ptr CChar)
pPpName
("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar))
-> ("statsString" ::: Ptr CChar)
-> ContT
("statsString" ::: Ptr CChar) IO ("statsString" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ("statsString" ::: Ptr CChar
ppName)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaSetPoolName" ffiVmaSetPoolName
:: Allocator -> Pool -> Ptr CChar -> IO ()
setPoolName :: forall io
. (MonadIO io)
=>
Allocator
->
Pool
->
("name" ::: Maybe ByteString)
-> io ()
setPoolName :: Allocator -> Pool -> ("name" ::: Maybe ByteString) -> io ()
setPoolName allocator :: Allocator
allocator pool :: Pool
pool name :: "name" ::: Maybe ByteString
name = 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
"statsString" ::: Ptr CChar
pName <- case ("name" ::: Maybe ByteString
name) of
Nothing -> ("statsString" ::: Ptr CChar)
-> ContT () IO ("statsString" ::: Ptr CChar)
forall (f :: * -> *) a. Applicative f => a -> f a
pure "statsString" ::: Ptr CChar
forall a. Ptr a
nullPtr
Just j :: ByteString
j -> ((("statsString" ::: Ptr CChar) -> IO ()) -> IO ())
-> ContT () IO ("statsString" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("statsString" ::: Ptr CChar) -> IO ()) -> IO ())
-> ContT () IO ("statsString" ::: Ptr CChar))
-> ((("statsString" ::: Ptr CChar) -> IO ()) -> IO ())
-> ContT () IO ("statsString" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ByteString -> (("statsString" ::: Ptr CChar) -> IO ()) -> IO ()
forall a.
ByteString -> (("statsString" ::: Ptr CChar) -> IO a) -> IO a
useAsCString (ByteString
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
$ (Allocator -> Pool -> ("statsString" ::: Ptr CChar) -> IO ()
ffiVmaSetPoolName) (Allocator
allocator) (Pool
pool) "statsString" ::: Ptr CChar
pName
() -> 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
"vmaAllocateMemory" ffiVmaAllocateMemory
:: Allocator -> Ptr MemoryRequirements -> Ptr AllocationCreateInfo -> Ptr Allocation -> Ptr AllocationInfo -> IO Result
allocateMemory :: forall io
. (MonadIO io)
=>
Allocator
->
("vkMemoryRequirements" ::: MemoryRequirements)
->
AllocationCreateInfo
-> io (Allocation, AllocationInfo)
allocateMemory :: Allocator
-> ("vkMemoryRequirements" ::: MemoryRequirements)
-> AllocationCreateInfo
-> io (Allocation, AllocationInfo)
allocateMemory allocator :: Allocator
allocator vkMemoryRequirements :: "vkMemoryRequirements" ::: MemoryRequirements
vkMemoryRequirements createInfo :: AllocationCreateInfo
createInfo = IO (Allocation, AllocationInfo) -> io (Allocation, AllocationInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo))
-> (ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> IO (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> IO (Allocation, AllocationInfo)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ do
Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
pVkMemoryRequirements <- ((Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo)
IO
(Ptr ("vkMemoryRequirements" ::: MemoryRequirements))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo)
IO
(Ptr ("vkMemoryRequirements" ::: MemoryRequirements)))
-> ((Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo)
IO
(Ptr ("vkMemoryRequirements" ::: MemoryRequirements))
forall a b. (a -> b) -> a -> b
$ ("vkMemoryRequirements" ::: MemoryRequirements)
-> (Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct ("vkMemoryRequirements" ::: MemoryRequirements
vkMemoryRequirements)
Ptr AllocationCreateInfo
pCreateInfo <- ((Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo))
-> ((Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall a b. (a -> b) -> a -> b
$ AllocationCreateInfo
-> (Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCreateInfo
createInfo)
Ptr Allocation
pPAllocation <- ((Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr Allocation))
-> ((Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Allocation)
-> (Ptr Allocation -> IO ())
-> (Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Allocation)
forall a. Int -> IO (Ptr a)
callocBytes @Allocation 8) Ptr Allocation -> IO ()
forall a. Ptr a -> IO ()
free
Ptr AllocationInfo
pPAllocationInfo <- ((Ptr AllocationInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr AllocationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct AllocationInfo =>
(Ptr AllocationInfo -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @AllocationInfo)
Result
r <- IO Result -> ContT (Allocation, AllocationInfo) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Allocation, AllocationInfo) IO Result)
-> IO Result -> ContT (Allocation, AllocationInfo) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> Ptr AllocationCreateInfo
-> Ptr Allocation
-> Ptr AllocationInfo
-> IO Result
ffiVmaAllocateMemory) (Allocator
allocator) Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
pVkMemoryRequirements Ptr AllocationCreateInfo
pCreateInfo (Ptr Allocation
pPAllocation) (Ptr AllocationInfo
pPAllocationInfo)
IO () -> ContT (Allocation, AllocationInfo) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Allocation, AllocationInfo) IO ())
-> IO () -> ContT (Allocation, AllocationInfo) 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))
Allocation
pAllocation <- IO Allocation -> ContT (Allocation, AllocationInfo) IO Allocation
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Allocation -> ContT (Allocation, AllocationInfo) IO Allocation)
-> IO Allocation
-> ContT (Allocation, AllocationInfo) IO Allocation
forall a b. (a -> b) -> a -> b
$ Ptr Allocation -> IO Allocation
forall a. Storable a => Ptr a -> IO a
peek @Allocation Ptr Allocation
pPAllocation
AllocationInfo
pAllocationInfo <- IO AllocationInfo
-> ContT (Allocation, AllocationInfo) IO AllocationInfo
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO AllocationInfo
-> ContT (Allocation, AllocationInfo) IO AllocationInfo)
-> IO AllocationInfo
-> ContT (Allocation, AllocationInfo) IO AllocationInfo
forall a b. (a -> b) -> a -> b
$ Ptr AllocationInfo -> IO AllocationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AllocationInfo Ptr AllocationInfo
pPAllocationInfo
(Allocation, AllocationInfo)
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Allocation, AllocationInfo)
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo))
-> (Allocation, AllocationInfo)
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ (Allocation
pAllocation, AllocationInfo
pAllocationInfo)
withMemory :: forall io r . MonadIO io => Allocator -> MemoryRequirements -> AllocationCreateInfo -> (io (Allocation, AllocationInfo) -> ((Allocation, AllocationInfo) -> io ()) -> r) -> r
withMemory :: Allocator
-> ("vkMemoryRequirements" ::: MemoryRequirements)
-> AllocationCreateInfo
-> (io (Allocation, AllocationInfo)
-> ((Allocation, AllocationInfo) -> io ()) -> r)
-> r
withMemory allocator :: Allocator
allocator pVkMemoryRequirements :: "vkMemoryRequirements" ::: MemoryRequirements
pVkMemoryRequirements pCreateInfo :: AllocationCreateInfo
pCreateInfo b :: io (Allocation, AllocationInfo)
-> ((Allocation, AllocationInfo) -> io ()) -> r
b =
io (Allocation, AllocationInfo)
-> ((Allocation, AllocationInfo) -> io ()) -> r
b (Allocator
-> ("vkMemoryRequirements" ::: MemoryRequirements)
-> AllocationCreateInfo
-> io (Allocation, AllocationInfo)
forall (io :: * -> *).
MonadIO io =>
Allocator
-> ("vkMemoryRequirements" ::: MemoryRequirements)
-> AllocationCreateInfo
-> io (Allocation, AllocationInfo)
allocateMemory Allocator
allocator "vkMemoryRequirements" ::: MemoryRequirements
pVkMemoryRequirements AllocationCreateInfo
pCreateInfo)
(\(o0 :: Allocation
o0, _) -> Allocator -> Allocation -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> Allocation -> io ()
freeMemory Allocator
allocator Allocation
o0)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaAllocateMemoryPages" ffiVmaAllocateMemoryPages
:: Allocator -> Ptr MemoryRequirements -> Ptr AllocationCreateInfo -> CSize -> Ptr Allocation -> Ptr AllocationInfo -> IO Result
allocateMemoryPages :: forall io
. (MonadIO io)
=>
Allocator
->
("vkMemoryRequirements" ::: Vector MemoryRequirements)
->
("createInfo" ::: Vector AllocationCreateInfo)
-> io (("allocations" ::: Vector Allocation), ("allocationInfo" ::: Vector AllocationInfo))
allocateMemoryPages :: Allocator
-> ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements))
-> ("createInfo" ::: Vector AllocationCreateInfo)
-> io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
allocateMemoryPages allocator :: Allocator
allocator vkMemoryRequirements :: "vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements)
vkMemoryRequirements createInfo :: "createInfo" ::: Vector AllocationCreateInfo
createInfo = IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> (ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b. (a -> b) -> a -> b
$ do
Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
pPVkMemoryRequirements <- ((Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr ("vkMemoryRequirements" ::: MemoryRequirements))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr ("vkMemoryRequirements" ::: MemoryRequirements)))
-> ((Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr ("vkMemoryRequirements" ::: MemoryRequirements))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @MemoryRequirements ((("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements))
-> Int
forall a. Vector a -> Int
Data.Vector.length ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements)
vkMemoryRequirements)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 24) 8
(Int
-> ("vkMemoryRequirements" ::: MemoryRequirements)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
())
-> ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "vkMemoryRequirements" ::: MemoryRequirements
e -> ((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
())
-> ((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall a b. (a -> b) -> a -> b
$ Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> ("vkMemoryRequirements" ::: MemoryRequirements)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct (Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
pPVkMemoryRequirements Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> Int -> Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr MemoryRequirements) ("vkMemoryRequirements" ::: MemoryRequirements
e) (IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> (()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b. (a -> b) -> a -> b
$ ())) ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements)
vkMemoryRequirements)
Ptr AllocationCreateInfo
pPCreateInfo <- ((Ptr AllocationCreateInfo
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr AllocationCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCreateInfo
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr AllocationCreateInfo))
-> ((Ptr AllocationCreateInfo
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr AllocationCreateInfo)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr AllocationCreateInfo
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @AllocationCreateInfo ((("createInfo" ::: Vector AllocationCreateInfo) -> Int
forall a. Vector a -> Int
Data.Vector.length ("createInfo" ::: Vector AllocationCreateInfo
createInfo)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 40) 8
IO ()
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
())
-> IO ()
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall a b. (a -> b) -> a -> b
$ (Int -> AllocationCreateInfo -> IO ())
-> ("createInfo" ::: Vector AllocationCreateInfo) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: AllocationCreateInfo
e -> Ptr AllocationCreateInfo -> AllocationCreateInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr AllocationCreateInfo
pPCreateInfo Ptr AllocationCreateInfo -> Int -> Ptr AllocationCreateInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (40 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AllocationCreateInfo) (AllocationCreateInfo
e)) ("createInfo" ::: Vector AllocationCreateInfo
createInfo)
let pVkMemoryRequirementsLength :: Int
pVkMemoryRequirementsLength = ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements))
-> Int
forall a. Vector a -> Int
Data.Vector.length (("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements))
-> Int)
-> ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements))
-> Int
forall a b. (a -> b) -> a -> b
$ ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements)
vkMemoryRequirements)
IO ()
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
())
-> IO ()
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall a b. (a -> b) -> a -> b
$ Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((("createInfo" ::: Vector AllocationCreateInfo) -> Int
forall a. Vector a -> Int
Data.Vector.length (("createInfo" ::: Vector AllocationCreateInfo) -> Int)
-> ("createInfo" ::: Vector AllocationCreateInfo) -> Int
forall a b. (a -> b) -> a -> b
$ ("createInfo" ::: Vector AllocationCreateInfo
createInfo)) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
pVkMemoryRequirementsLength) (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 "" "pCreateInfo and pVkMemoryRequirements must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
Ptr Allocation
pPAllocations <- ((Ptr Allocation
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr Allocation))
-> ((Ptr Allocation
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Allocation)
-> (Ptr Allocation -> IO ())
-> (Ptr Allocation
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Allocation)
forall a. Int -> IO (Ptr a)
callocBytes @Allocation ((CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pVkMemoryRequirementsLength :: CSize))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8)) Ptr Allocation -> IO ()
forall a. Ptr a -> IO ()
free
Ptr AllocationInfo
pPAllocationInfo <- ((Ptr AllocationInfo
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr AllocationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationInfo
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr AllocationInfo))
-> ((Ptr AllocationInfo
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
(Ptr AllocationInfo)
forall a b. (a -> b) -> a -> b
$ IO (Ptr AllocationInfo)
-> (Ptr AllocationInfo -> IO ())
-> (Ptr AllocationInfo
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr AllocationInfo)
forall a. Int -> IO (Ptr a)
callocBytes @AllocationInfo ((CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pVkMemoryRequirementsLength :: CSize))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48)) Ptr AllocationInfo -> IO ()
forall a. Ptr a -> IO ()
free
[()]
_ <- (Int
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
())
-> [Int]
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
[()]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (\i :: Int
i -> ((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
())
-> ((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall a b. (a -> b) -> a -> b
$ Ptr AllocationInfo
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b. ToCStruct a => Ptr a -> IO b -> IO b
pokeZeroCStruct (Ptr AllocationInfo
pPAllocationInfo Ptr AllocationInfo -> Int -> Ptr AllocationInfo
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
* 48) :: Ptr AllocationInfo) (IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> (()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ()
-> IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b. (a -> b) -> a -> b
$ ())) [0..(CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pVkMemoryRequirementsLength :: CSize))) Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1]
Result
r <- IO Result
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
Result)
-> IO Result
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
-> Ptr AllocationCreateInfo
-> CSize
-> Ptr Allocation
-> Ptr AllocationInfo
-> IO Result
ffiVmaAllocateMemoryPages) (Allocator
allocator) (Ptr ("vkMemoryRequirements" ::: MemoryRequirements)
pPVkMemoryRequirements) (Ptr AllocationCreateInfo
pPCreateInfo) ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pVkMemoryRequirementsLength :: CSize)) (Ptr Allocation
pPAllocations) ((Ptr AllocationInfo
pPAllocationInfo))
IO ()
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
())
-> IO ()
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
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))
"allocations" ::: Vector Allocation
pAllocations <- IO ("allocations" ::: Vector Allocation)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("allocations" ::: Vector Allocation)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation))
-> IO ("allocations" ::: Vector Allocation)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO Allocation)
-> IO ("allocations" ::: Vector Allocation)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pVkMemoryRequirementsLength :: CSize))) (\i :: Int
i -> Ptr Allocation -> IO Allocation
forall a. Storable a => Ptr a -> IO a
peek @Allocation ((Ptr Allocation
pPAllocations Ptr Allocation -> Int -> Ptr Allocation
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Allocation)))
"allocationInfo" ::: Vector AllocationInfo
pAllocationInfo <- IO ("allocationInfo" ::: Vector AllocationInfo)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocationInfo" ::: Vector AllocationInfo)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("allocationInfo" ::: Vector AllocationInfo)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocationInfo" ::: Vector AllocationInfo))
-> IO ("allocationInfo" ::: Vector AllocationInfo)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocationInfo" ::: Vector AllocationInfo)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO AllocationInfo)
-> IO ("allocationInfo" ::: Vector AllocationInfo)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
pVkMemoryRequirementsLength :: CSize))) (\i :: Int
i -> Ptr AllocationInfo -> IO AllocationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AllocationInfo (((Ptr AllocationInfo
pPAllocationInfo) Ptr AllocationInfo -> Int -> Ptr AllocationInfo
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (48 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr AllocationInfo)))
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo))
-> ("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> ContT
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
IO
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall a b. (a -> b) -> a -> b
$ ("allocations" ::: Vector Allocation
pAllocations, "allocationInfo" ::: Vector AllocationInfo
pAllocationInfo)
withMemoryPages :: forall io r . MonadIO io => Allocator -> Vector MemoryRequirements -> Vector AllocationCreateInfo -> (io (Vector Allocation, Vector AllocationInfo) -> ((Vector Allocation, Vector AllocationInfo) -> io ()) -> r) -> r
withMemoryPages :: Allocator
-> ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements))
-> ("createInfo" ::: Vector AllocationCreateInfo)
-> (io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> (("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> io ())
-> r)
-> r
withMemoryPages allocator :: Allocator
allocator pVkMemoryRequirements :: "vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements)
pVkMemoryRequirements pCreateInfo :: "createInfo" ::: Vector AllocationCreateInfo
pCreateInfo b :: io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> (("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> io ())
-> r
b =
io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> (("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
-> io ())
-> r
b (Allocator
-> ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements))
-> ("createInfo" ::: Vector AllocationCreateInfo)
-> io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
forall (io :: * -> *).
MonadIO io =>
Allocator
-> ("vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements))
-> ("createInfo" ::: Vector AllocationCreateInfo)
-> io
("allocations" ::: Vector Allocation,
"allocationInfo" ::: Vector AllocationInfo)
allocateMemoryPages Allocator
allocator "vkMemoryRequirements"
::: Vector ("vkMemoryRequirements" ::: MemoryRequirements)
pVkMemoryRequirements "createInfo" ::: Vector AllocationCreateInfo
pCreateInfo)
(\(o0 :: "allocations" ::: Vector Allocation
o0, _) -> Allocator -> ("allocations" ::: Vector Allocation) -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> ("allocations" ::: Vector Allocation) -> io ()
freeMemoryPages Allocator
allocator "allocations" ::: Vector Allocation
o0)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaAllocateMemoryForBuffer" ffiVmaAllocateMemoryForBuffer
:: Allocator -> Buffer -> Ptr AllocationCreateInfo -> Ptr Allocation -> Ptr AllocationInfo -> IO Result
allocateMemoryForBuffer :: forall io
. (MonadIO io)
=>
Allocator
->
Buffer
->
AllocationCreateInfo
-> io (Allocation, AllocationInfo)
allocateMemoryForBuffer :: Allocator
-> Buffer
-> AllocationCreateInfo
-> io (Allocation, AllocationInfo)
allocateMemoryForBuffer allocator :: Allocator
allocator buffer :: Buffer
buffer createInfo :: AllocationCreateInfo
createInfo = IO (Allocation, AllocationInfo) -> io (Allocation, AllocationInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo))
-> (ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> IO (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> IO (Allocation, AllocationInfo)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ do
Ptr AllocationCreateInfo
pCreateInfo <- ((Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo))
-> ((Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall a b. (a -> b) -> a -> b
$ AllocationCreateInfo
-> (Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCreateInfo
createInfo)
Ptr Allocation
pPAllocation <- ((Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr Allocation))
-> ((Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Allocation)
-> (Ptr Allocation -> IO ())
-> (Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Allocation)
forall a. Int -> IO (Ptr a)
callocBytes @Allocation 8) Ptr Allocation -> IO ()
forall a. Ptr a -> IO ()
free
Ptr AllocationInfo
pPAllocationInfo <- ((Ptr AllocationInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr AllocationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct AllocationInfo =>
(Ptr AllocationInfo -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @AllocationInfo)
Result
r <- IO Result -> ContT (Allocation, AllocationInfo) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Allocation, AllocationInfo) IO Result)
-> IO Result -> ContT (Allocation, AllocationInfo) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Buffer
-> Ptr AllocationCreateInfo
-> Ptr Allocation
-> Ptr AllocationInfo
-> IO Result
ffiVmaAllocateMemoryForBuffer) (Allocator
allocator) (Buffer
buffer) Ptr AllocationCreateInfo
pCreateInfo (Ptr Allocation
pPAllocation) (Ptr AllocationInfo
pPAllocationInfo)
IO () -> ContT (Allocation, AllocationInfo) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Allocation, AllocationInfo) IO ())
-> IO () -> ContT (Allocation, AllocationInfo) 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))
Allocation
pAllocation <- IO Allocation -> ContT (Allocation, AllocationInfo) IO Allocation
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Allocation -> ContT (Allocation, AllocationInfo) IO Allocation)
-> IO Allocation
-> ContT (Allocation, AllocationInfo) IO Allocation
forall a b. (a -> b) -> a -> b
$ Ptr Allocation -> IO Allocation
forall a. Storable a => Ptr a -> IO a
peek @Allocation Ptr Allocation
pPAllocation
AllocationInfo
pAllocationInfo <- IO AllocationInfo
-> ContT (Allocation, AllocationInfo) IO AllocationInfo
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO AllocationInfo
-> ContT (Allocation, AllocationInfo) IO AllocationInfo)
-> IO AllocationInfo
-> ContT (Allocation, AllocationInfo) IO AllocationInfo
forall a b. (a -> b) -> a -> b
$ Ptr AllocationInfo -> IO AllocationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AllocationInfo Ptr AllocationInfo
pPAllocationInfo
(Allocation, AllocationInfo)
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Allocation, AllocationInfo)
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo))
-> (Allocation, AllocationInfo)
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ (Allocation
pAllocation, AllocationInfo
pAllocationInfo)
withMemoryForBuffer :: forall io r . MonadIO io => Allocator -> Buffer -> AllocationCreateInfo -> (io (Allocation, AllocationInfo) -> ((Allocation, AllocationInfo) -> io ()) -> r) -> r
withMemoryForBuffer :: Allocator
-> Buffer
-> AllocationCreateInfo
-> (io (Allocation, AllocationInfo)
-> ((Allocation, AllocationInfo) -> io ()) -> r)
-> r
withMemoryForBuffer allocator :: Allocator
allocator buffer :: Buffer
buffer pCreateInfo :: AllocationCreateInfo
pCreateInfo b :: io (Allocation, AllocationInfo)
-> ((Allocation, AllocationInfo) -> io ()) -> r
b =
io (Allocation, AllocationInfo)
-> ((Allocation, AllocationInfo) -> io ()) -> r
b (Allocator
-> Buffer
-> AllocationCreateInfo
-> io (Allocation, AllocationInfo)
forall (io :: * -> *).
MonadIO io =>
Allocator
-> Buffer
-> AllocationCreateInfo
-> io (Allocation, AllocationInfo)
allocateMemoryForBuffer Allocator
allocator Buffer
buffer AllocationCreateInfo
pCreateInfo)
(\(o0 :: Allocation
o0, _) -> Allocator -> Allocation -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> Allocation -> io ()
freeMemory Allocator
allocator Allocation
o0)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaAllocateMemoryForImage" ffiVmaAllocateMemoryForImage
:: Allocator -> Image -> Ptr AllocationCreateInfo -> Ptr Allocation -> Ptr AllocationInfo -> IO Result
allocateMemoryForImage :: forall io
. (MonadIO io)
=>
Allocator
->
Image
->
AllocationCreateInfo
-> io (Allocation, AllocationInfo)
allocateMemoryForImage :: Allocator
-> Image -> AllocationCreateInfo -> io (Allocation, AllocationInfo)
allocateMemoryForImage allocator :: Allocator
allocator image :: Image
image createInfo :: AllocationCreateInfo
createInfo = IO (Allocation, AllocationInfo) -> io (Allocation, AllocationInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo))
-> (ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> IO (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT (Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> IO (Allocation, AllocationInfo)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT (Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
-> io (Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ do
Ptr AllocationCreateInfo
pCreateInfo <- ((Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT
(Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo))
-> ((Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall a b. (a -> b) -> a -> b
$ AllocationCreateInfo
-> (Ptr AllocationCreateInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCreateInfo
createInfo)
Ptr Allocation
pPAllocation <- ((Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr Allocation))
-> ((Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Allocation)
-> (Ptr Allocation -> IO ())
-> (Ptr Allocation -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Allocation)
forall a. Int -> IO (Ptr a)
callocBytes @Allocation 8) Ptr Allocation -> IO ()
forall a. Ptr a -> IO ()
free
Ptr AllocationInfo
pPAllocationInfo <- ((Ptr AllocationInfo -> IO (Allocation, AllocationInfo))
-> IO (Allocation, AllocationInfo))
-> ContT (Allocation, AllocationInfo) IO (Ptr AllocationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct AllocationInfo =>
(Ptr AllocationInfo -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @AllocationInfo)
Result
r <- IO Result -> ContT (Allocation, AllocationInfo) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Allocation, AllocationInfo) IO Result)
-> IO Result -> ContT (Allocation, AllocationInfo) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Image
-> Ptr AllocationCreateInfo
-> Ptr Allocation
-> Ptr AllocationInfo
-> IO Result
ffiVmaAllocateMemoryForImage) (Allocator
allocator) (Image
image) Ptr AllocationCreateInfo
pCreateInfo (Ptr Allocation
pPAllocation) (Ptr AllocationInfo
pPAllocationInfo)
IO () -> ContT (Allocation, AllocationInfo) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Allocation, AllocationInfo) IO ())
-> IO () -> ContT (Allocation, AllocationInfo) 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))
Allocation
pAllocation <- IO Allocation -> ContT (Allocation, AllocationInfo) IO Allocation
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Allocation -> ContT (Allocation, AllocationInfo) IO Allocation)
-> IO Allocation
-> ContT (Allocation, AllocationInfo) IO Allocation
forall a b. (a -> b) -> a -> b
$ Ptr Allocation -> IO Allocation
forall a. Storable a => Ptr a -> IO a
peek @Allocation Ptr Allocation
pPAllocation
AllocationInfo
pAllocationInfo <- IO AllocationInfo
-> ContT (Allocation, AllocationInfo) IO AllocationInfo
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO AllocationInfo
-> ContT (Allocation, AllocationInfo) IO AllocationInfo)
-> IO AllocationInfo
-> ContT (Allocation, AllocationInfo) IO AllocationInfo
forall a b. (a -> b) -> a -> b
$ Ptr AllocationInfo -> IO AllocationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AllocationInfo Ptr AllocationInfo
pPAllocationInfo
(Allocation, AllocationInfo)
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Allocation, AllocationInfo)
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo))
-> (Allocation, AllocationInfo)
-> ContT
(Allocation, AllocationInfo) IO (Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ (Allocation
pAllocation, AllocationInfo
pAllocationInfo)
withMemoryForImage :: forall io r . MonadIO io => Allocator -> Image -> AllocationCreateInfo -> (io (Allocation, AllocationInfo) -> ((Allocation, AllocationInfo) -> io ()) -> r) -> r
withMemoryForImage :: Allocator
-> Image
-> AllocationCreateInfo
-> (io (Allocation, AllocationInfo)
-> ((Allocation, AllocationInfo) -> io ()) -> r)
-> r
withMemoryForImage allocator :: Allocator
allocator image :: Image
image pCreateInfo :: AllocationCreateInfo
pCreateInfo b :: io (Allocation, AllocationInfo)
-> ((Allocation, AllocationInfo) -> io ()) -> r
b =
io (Allocation, AllocationInfo)
-> ((Allocation, AllocationInfo) -> io ()) -> r
b (Allocator
-> Image -> AllocationCreateInfo -> io (Allocation, AllocationInfo)
forall (io :: * -> *).
MonadIO io =>
Allocator
-> Image -> AllocationCreateInfo -> io (Allocation, AllocationInfo)
allocateMemoryForImage Allocator
allocator Image
image AllocationCreateInfo
pCreateInfo)
(\(o0 :: Allocation
o0, _) -> Allocator -> Allocation -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> Allocation -> io ()
freeMemory Allocator
allocator Allocation
o0)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaFreeMemory" ffiVmaFreeMemory
:: Allocator -> Allocation -> IO ()
freeMemory :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
-> io ()
freeMemory :: Allocator -> Allocation -> io ()
freeMemory allocator :: Allocator
allocator allocation :: Allocation
allocation = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
(Allocator -> Allocation -> IO ()
ffiVmaFreeMemory) (Allocator
allocator) (Allocation
allocation)
() -> 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
"vmaFreeMemoryPages" ffiVmaFreeMemoryPages
:: Allocator -> CSize -> Ptr Allocation -> IO ()
freeMemoryPages :: forall io
. (MonadIO io)
=>
Allocator
->
("allocations" ::: Vector Allocation)
-> io ()
freeMemoryPages :: Allocator -> ("allocations" ::: Vector Allocation) -> io ()
freeMemoryPages allocator :: Allocator
allocator allocations :: "allocations" ::: Vector Allocation
allocations = 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
Ptr Allocation
pPAllocations <- ((Ptr Allocation -> IO ()) -> IO ())
-> ContT () IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO ()) -> IO ())
-> ContT () IO (Ptr Allocation))
-> ((Ptr Allocation -> IO ()) -> IO ())
-> ContT () IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Allocation -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Allocation ((("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length ("allocations" ::: Vector Allocation
allocations)) 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 -> Allocation -> IO ())
-> ("allocations" ::: Vector Allocation) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Allocation
e -> Ptr Allocation -> Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Allocation
pPAllocations Ptr Allocation -> Int -> Ptr Allocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Allocation) (Allocation
e)) ("allocations" ::: Vector Allocation
allocations)
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
$ (Allocator -> CSize -> Ptr Allocation -> IO ()
ffiVmaFreeMemoryPages) (Allocator
allocator) ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length (("allocations" ::: Vector Allocation) -> Int)
-> ("allocations" ::: Vector Allocation) -> Int
forall a b. (a -> b) -> a -> b
$ ("allocations" ::: Vector Allocation
allocations)) :: CSize)) (Ptr Allocation
pPAllocations)
() -> 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
"vmaResizeAllocation" ffiVmaResizeAllocation
:: Allocator -> Allocation -> DeviceSize -> IO Result
resizeAllocation :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
->
("newSize" ::: DeviceSize)
-> io ()
resizeAllocation :: Allocator
-> Allocation -> ("lostAllocationCount" ::: Word64) -> io ()
resizeAllocation allocator :: Allocator
allocator allocation :: Allocation
allocation newSize :: "lostAllocationCount" ::: Word64
newSize = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator
-> Allocation -> ("lostAllocationCount" ::: Word64) -> IO Result
ffiVmaResizeAllocation) (Allocator
allocator) (Allocation
allocation) ("lostAllocationCount" ::: Word64
newSize)
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
"vmaGetAllocationInfo" ffiVmaGetAllocationInfo
:: Allocator -> Allocation -> Ptr AllocationInfo -> IO ()
getAllocationInfo :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
-> io (AllocationInfo)
getAllocationInfo :: Allocator -> Allocation -> io AllocationInfo
getAllocationInfo allocator :: Allocator
allocator allocation :: Allocation
allocation = IO AllocationInfo -> io AllocationInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AllocationInfo -> io AllocationInfo)
-> (ContT AllocationInfo IO AllocationInfo -> IO AllocationInfo)
-> ContT AllocationInfo IO AllocationInfo
-> io AllocationInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT AllocationInfo IO AllocationInfo -> IO AllocationInfo
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT AllocationInfo IO AllocationInfo -> io AllocationInfo)
-> ContT AllocationInfo IO AllocationInfo -> io AllocationInfo
forall a b. (a -> b) -> a -> b
$ do
Ptr AllocationInfo
pPAllocationInfo <- ((Ptr AllocationInfo -> IO AllocationInfo) -> IO AllocationInfo)
-> ContT AllocationInfo IO (Ptr AllocationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct AllocationInfo =>
(Ptr AllocationInfo -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @AllocationInfo)
IO () -> ContT AllocationInfo IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT AllocationInfo IO ())
-> IO () -> ContT AllocationInfo IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Allocation -> Ptr AllocationInfo -> IO ()
ffiVmaGetAllocationInfo) (Allocator
allocator) (Allocation
allocation) (Ptr AllocationInfo
pPAllocationInfo)
AllocationInfo
pAllocationInfo <- IO AllocationInfo -> ContT AllocationInfo IO AllocationInfo
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO AllocationInfo -> ContT AllocationInfo IO AllocationInfo)
-> IO AllocationInfo -> ContT AllocationInfo IO AllocationInfo
forall a b. (a -> b) -> a -> b
$ Ptr AllocationInfo -> IO AllocationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AllocationInfo Ptr AllocationInfo
pPAllocationInfo
AllocationInfo -> ContT AllocationInfo IO AllocationInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AllocationInfo -> ContT AllocationInfo IO AllocationInfo)
-> AllocationInfo -> ContT AllocationInfo IO AllocationInfo
forall a b. (a -> b) -> a -> b
$ (AllocationInfo
pAllocationInfo)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaTouchAllocation" ffiVmaTouchAllocation
:: Allocator -> Allocation -> IO Bool32
touchAllocation :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
-> io (Bool)
touchAllocation :: Allocator -> Allocation -> io Bool
touchAllocation allocator :: Allocator
allocator allocation :: Allocation
allocation = IO Bool -> io Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> io Bool) -> IO Bool -> io Bool
forall a b. (a -> b) -> a -> b
$ do
Bool32
r <- (Allocator -> Allocation -> IO Bool32
ffiVmaTouchAllocation) (Allocator
allocator) (Allocation
allocation)
Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ ((Bool32 -> Bool
bool32ToBool Bool32
r))
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaSetAllocationUserData" ffiVmaSetAllocationUserData
:: Allocator -> Allocation -> Ptr () -> IO ()
setAllocationUserData :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
->
("userData" ::: Ptr ())
-> io ()
setAllocationUserData :: Allocator -> Allocation -> ("userData" ::: Ptr ()) -> io ()
setAllocationUserData allocator :: Allocator
allocator allocation :: Allocation
allocation userData :: "userData" ::: Ptr ()
userData = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
(Allocator -> Allocation -> ("userData" ::: Ptr ()) -> IO ()
ffiVmaSetAllocationUserData) (Allocator
allocator) (Allocation
allocation) ("userData" ::: Ptr ()
userData)
() -> 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
"vmaCreateLostAllocation" ffiVmaCreateLostAllocation
:: Allocator -> Ptr Allocation -> IO ()
createLostAllocation :: forall io
. (MonadIO io)
=>
Allocator
-> io (Allocation)
createLostAllocation :: Allocator -> io Allocation
createLostAllocation allocator :: Allocator
allocator = IO Allocation -> io Allocation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Allocation -> io Allocation)
-> (ContT Allocation IO Allocation -> IO Allocation)
-> ContT Allocation IO Allocation
-> io Allocation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT Allocation IO Allocation -> IO Allocation
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT Allocation IO Allocation -> io Allocation)
-> ContT Allocation IO Allocation -> io Allocation
forall a b. (a -> b) -> a -> b
$ do
Ptr Allocation
pPAllocation <- ((Ptr Allocation -> IO Allocation) -> IO Allocation)
-> ContT Allocation IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO Allocation) -> IO Allocation)
-> ContT Allocation IO (Ptr Allocation))
-> ((Ptr Allocation -> IO Allocation) -> IO Allocation)
-> ContT Allocation IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Allocation)
-> (Ptr Allocation -> IO ())
-> (Ptr Allocation -> IO Allocation)
-> IO Allocation
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Allocation)
forall a. Int -> IO (Ptr a)
callocBytes @Allocation 8) Ptr Allocation -> IO ()
forall a. Ptr a -> IO ()
free
IO () -> ContT Allocation IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT Allocation IO ())
-> IO () -> ContT Allocation IO ()
forall a b. (a -> b) -> a -> b
$ (Allocator -> Ptr Allocation -> IO ()
ffiVmaCreateLostAllocation) (Allocator
allocator) (Ptr Allocation
pPAllocation)
Allocation
pAllocation <- IO Allocation -> ContT Allocation IO Allocation
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Allocation -> ContT Allocation IO Allocation)
-> IO Allocation -> ContT Allocation IO Allocation
forall a b. (a -> b) -> a -> b
$ Ptr Allocation -> IO Allocation
forall a. Storable a => Ptr a -> IO a
peek @Allocation Ptr Allocation
pPAllocation
Allocation -> ContT Allocation IO Allocation
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Allocation -> ContT Allocation IO Allocation)
-> Allocation -> ContT Allocation IO Allocation
forall a b. (a -> b) -> a -> b
$ (Allocation
pAllocation)
withLostAllocation :: forall io r . MonadIO io => Allocator -> (io (Allocation) -> ((Allocation) -> io ()) -> r) -> r
withLostAllocation :: Allocator -> (io Allocation -> (Allocation -> io ()) -> r) -> r
withLostAllocation allocator :: Allocator
allocator b :: io Allocation -> (Allocation -> io ()) -> r
b =
io Allocation -> (Allocation -> io ()) -> r
b (Allocator -> io Allocation
forall (io :: * -> *). MonadIO io => Allocator -> io Allocation
createLostAllocation Allocator
allocator)
(\(Allocation
o0) -> Allocator -> Allocation -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> Allocation -> io ()
freeMemory Allocator
allocator Allocation
o0)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaMapMemory" ffiVmaMapMemory
:: Allocator -> Allocation -> Ptr (Ptr ()) -> IO Result
mapMemory :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
-> io (("data" ::: Ptr ()))
mapMemory :: Allocator -> Allocation -> io ("userData" ::: Ptr ())
mapMemory allocator :: Allocator
allocator allocation :: Allocation
allocation = IO ("userData" ::: Ptr ()) -> io ("userData" ::: Ptr ())
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("userData" ::: Ptr ()) -> io ("userData" ::: Ptr ()))
-> (ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ())
-> IO ("userData" ::: Ptr ()))
-> ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ())
-> io ("userData" ::: Ptr ())
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ())
-> IO ("userData" ::: Ptr ())
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ())
-> io ("userData" ::: Ptr ()))
-> ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ())
-> io ("userData" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ do
Ptr ("userData" ::: Ptr ())
pPpData <- ((Ptr ("userData" ::: Ptr ()) -> IO ("userData" ::: Ptr ()))
-> IO ("userData" ::: Ptr ()))
-> ContT ("userData" ::: Ptr ()) IO (Ptr ("userData" ::: Ptr ()))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("userData" ::: Ptr ()) -> IO ("userData" ::: Ptr ()))
-> IO ("userData" ::: Ptr ()))
-> ContT ("userData" ::: Ptr ()) IO (Ptr ("userData" ::: Ptr ())))
-> ((Ptr ("userData" ::: Ptr ()) -> IO ("userData" ::: Ptr ()))
-> IO ("userData" ::: Ptr ()))
-> ContT ("userData" ::: Ptr ()) IO (Ptr ("userData" ::: Ptr ()))
forall a b. (a -> b) -> a -> b
$ IO (Ptr ("userData" ::: Ptr ()))
-> (Ptr ("userData" ::: Ptr ()) -> IO ())
-> (Ptr ("userData" ::: Ptr ()) -> IO ("userData" ::: Ptr ()))
-> IO ("userData" ::: Ptr ())
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr ("userData" ::: Ptr ()))
forall a. Int -> IO (Ptr a)
callocBytes @(Ptr ()) 8) Ptr ("userData" ::: Ptr ()) -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result -> ContT ("userData" ::: Ptr ()) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT ("userData" ::: Ptr ()) IO Result)
-> IO Result -> ContT ("userData" ::: Ptr ()) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator -> Allocation -> Ptr ("userData" ::: Ptr ()) -> IO Result
ffiVmaMapMemory) (Allocator
allocator) (Allocation
allocation) (Ptr ("userData" ::: Ptr ())
pPpData)
IO () -> ContT ("userData" ::: Ptr ()) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT ("userData" ::: Ptr ()) IO ())
-> IO () -> ContT ("userData" ::: 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))
"userData" ::: Ptr ()
ppData <- IO ("userData" ::: Ptr ())
-> ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ())
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("userData" ::: Ptr ())
-> ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ()))
-> IO ("userData" ::: Ptr ())
-> ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ Ptr ("userData" ::: Ptr ()) -> IO ("userData" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) Ptr ("userData" ::: Ptr ())
pPpData
("userData" ::: Ptr ())
-> ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ())
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("userData" ::: Ptr ())
-> ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ()))
-> ("userData" ::: Ptr ())
-> ContT ("userData" ::: Ptr ()) IO ("userData" ::: Ptr ())
forall a b. (a -> b) -> a -> b
$ ("userData" ::: Ptr ()
ppData)
withMappedMemory :: forall io r . MonadIO io => Allocator -> Allocation -> (io (Ptr ()) -> ((Ptr ()) -> io ()) -> r) -> r
withMappedMemory :: Allocator
-> Allocation
-> (io ("userData" ::: Ptr ())
-> (("userData" ::: Ptr ()) -> io ()) -> r)
-> r
withMappedMemory allocator :: Allocator
allocator allocation :: Allocation
allocation b :: io ("userData" ::: Ptr ())
-> (("userData" ::: Ptr ()) -> io ()) -> r
b =
io ("userData" ::: Ptr ())
-> (("userData" ::: Ptr ()) -> io ()) -> r
b (Allocator -> Allocation -> io ("userData" ::: Ptr ())
forall (io :: * -> *).
MonadIO io =>
Allocator -> Allocation -> io ("userData" ::: Ptr ())
mapMemory Allocator
allocator Allocation
allocation)
(\("userData" ::: Ptr ()
_) -> Allocator -> Allocation -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> Allocation -> io ()
unmapMemory Allocator
allocator Allocation
allocation)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaUnmapMemory" ffiVmaUnmapMemory
:: Allocator -> Allocation -> IO ()
unmapMemory :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
-> io ()
unmapMemory :: Allocator -> Allocation -> io ()
unmapMemory allocator :: Allocator
allocator allocation :: Allocation
allocation = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
(Allocator -> Allocation -> IO ()
ffiVmaUnmapMemory) (Allocator
allocator) (Allocation
allocation)
() -> 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
"vmaFlushAllocation" ffiVmaFlushAllocation
:: Allocator -> Allocation -> DeviceSize -> DeviceSize -> IO Result
flushAllocation :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
->
("offset" ::: DeviceSize)
->
DeviceSize
-> io ()
flushAllocation :: Allocator
-> Allocation
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> io ()
flushAllocation allocator :: Allocator
allocator allocation :: Allocation
allocation offset :: "lostAllocationCount" ::: Word64
offset size :: "lostAllocationCount" ::: Word64
size = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator
-> Allocation
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> IO Result
ffiVmaFlushAllocation) (Allocator
allocator) (Allocation
allocation) ("lostAllocationCount" ::: Word64
offset) ("lostAllocationCount" ::: Word64
size)
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
"vmaInvalidateAllocation" ffiVmaInvalidateAllocation
:: Allocator -> Allocation -> DeviceSize -> DeviceSize -> IO Result
invalidateAllocation :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
->
("offset" ::: DeviceSize)
->
DeviceSize
-> io ()
invalidateAllocation :: Allocator
-> Allocation
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> io ()
invalidateAllocation allocator :: Allocator
allocator allocation :: Allocation
allocation offset :: "lostAllocationCount" ::: Word64
offset size :: "lostAllocationCount" ::: Word64
size = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator
-> Allocation
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> IO Result
ffiVmaInvalidateAllocation) (Allocator
allocator) (Allocation
allocation) ("lostAllocationCount" ::: Word64
offset) ("lostAllocationCount" ::: Word64
size)
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
"vmaFlushAllocations" ffiVmaFlushAllocations
:: Allocator -> Word32 -> Ptr Allocation -> Ptr DeviceSize -> Ptr DeviceSize -> IO Result
flushAllocations :: forall io
. (MonadIO io)
=>
Allocator
->
("allocations" ::: Vector Allocation)
->
("offsets" ::: Vector DeviceSize)
->
("sizes" ::: Vector DeviceSize)
-> io ()
flushAllocations :: Allocator
-> ("allocations" ::: Vector Allocation)
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64))
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64))
-> io ()
flushAllocations allocator :: Allocator
allocator allocations :: "allocations" ::: Vector Allocation
allocations offsets :: "offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets sizes :: "offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes = 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 allocationsLength :: Int
allocationsLength = ("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length (("allocations" ::: Vector Allocation) -> Int)
-> ("allocations" ::: Vector Allocation) -> Int
forall a b. (a -> b) -> a -> b
$ ("allocations" ::: Vector Allocation
allocations)
let offsetsLength :: Int
offsetsLength = ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int)
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a b. (a -> b) -> a -> b
$ ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets)
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 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offsetsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
allocationsLength Bool -> Bool -> Bool
|| Int
offsetsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0) (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 "" "offsets and allocations must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let sizesLength :: Int
sizesLength = ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int)
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a b. (a -> b) -> a -> b
$ ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes)
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 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sizesLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
allocationsLength Bool -> Bool -> Bool
|| Int
sizesLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0) (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 "" "sizes and allocations must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
Ptr Allocation
pAllocations <- ((Ptr Allocation -> IO ()) -> IO ())
-> ContT () IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO ()) -> IO ())
-> ContT () IO (Ptr Allocation))
-> ((Ptr Allocation -> IO ()) -> IO ())
-> ContT () IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Allocation -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Allocation ((("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length ("allocations" ::: Vector Allocation
allocations)) 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 -> Allocation -> IO ())
-> ("allocations" ::: Vector Allocation) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Allocation
e -> Ptr Allocation -> Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Allocation
pAllocations Ptr Allocation -> Int -> Ptr Allocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Allocation) (Allocation
e)) ("allocations" ::: Vector Allocation
allocations)
Ptr ("lostAllocationCount" ::: Word64)
offsets' <- if ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Bool
forall a. Vector a -> Bool
Data.Vector.null ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets)
then Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr ("lostAllocationCount" ::: Word64)
forall a. Ptr a
nullPtr
else do
Ptr ("lostAllocationCount" ::: Word64)
pOffsets <- ((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64)))
-> ((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr ("lostAllocationCount" ::: Word64) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DeviceSize (((("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets))) 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 -> ("lostAllocationCount" ::: Word64) -> IO ())
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64))
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "lostAllocationCount" ::: Word64
e -> Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lostAllocationCount" ::: Word64)
pOffsets Ptr ("lostAllocationCount" ::: Word64)
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) ("lostAllocationCount" ::: Word64
e)) (("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets))
Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64)))
-> Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall a b. (a -> b) -> a -> b
$ Ptr ("lostAllocationCount" ::: Word64)
pOffsets
Ptr ("lostAllocationCount" ::: Word64)
sizes' <- if ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Bool
forall a. Vector a -> Bool
Data.Vector.null ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes)
then Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr ("lostAllocationCount" ::: Word64)
forall a. Ptr a
nullPtr
else do
Ptr ("lostAllocationCount" ::: Word64)
pSizes <- ((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64)))
-> ((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr ("lostAllocationCount" ::: Word64) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DeviceSize (((("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes))) 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 -> ("lostAllocationCount" ::: Word64) -> IO ())
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64))
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "lostAllocationCount" ::: Word64
e -> Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lostAllocationCount" ::: Word64)
pSizes Ptr ("lostAllocationCount" ::: Word64)
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) ("lostAllocationCount" ::: Word64
e)) (("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes))
Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64)))
-> Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall a b. (a -> b) -> a -> b
$ Ptr ("lostAllocationCount" ::: Word64)
pSizes
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
$ (Allocator
-> ("memoryTypeIndex" ::: Word32)
-> Ptr Allocation
-> Ptr ("lostAllocationCount" ::: Word64)
-> Ptr ("lostAllocationCount" ::: Word64)
-> IO Result
ffiVmaFlushAllocations) (Allocator
allocator) ((Int -> "memoryTypeIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
allocationsLength :: Word32)) (Ptr Allocation
pAllocations) Ptr ("lostAllocationCount" ::: Word64)
offsets' Ptr ("lostAllocationCount" ::: Word64)
sizes'
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
"vmaInvalidateAllocations" ffiVmaInvalidateAllocations
:: Allocator -> Word32 -> Ptr Allocation -> Ptr DeviceSize -> Ptr DeviceSize -> IO Result
invalidateAllocations :: forall io
. (MonadIO io)
=>
Allocator
->
("allocations" ::: Vector Allocation)
->
("offsets" ::: Vector DeviceSize)
->
("sizes" ::: Vector DeviceSize)
-> io ()
invalidateAllocations :: Allocator
-> ("allocations" ::: Vector Allocation)
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64))
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64))
-> io ()
invalidateAllocations allocator :: Allocator
allocator allocations :: "allocations" ::: Vector Allocation
allocations offsets :: "offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets sizes :: "offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes = 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 allocationsLength :: Int
allocationsLength = ("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length (("allocations" ::: Vector Allocation) -> Int)
-> ("allocations" ::: Vector Allocation) -> Int
forall a b. (a -> b) -> a -> b
$ ("allocations" ::: Vector Allocation
allocations)
let offsetsLength :: Int
offsetsLength = ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int)
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a b. (a -> b) -> a -> b
$ ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets)
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 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
offsetsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
allocationsLength Bool -> Bool -> Bool
|| Int
offsetsLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0) (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 "" "offsets and allocations must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
let sizesLength :: Int
sizesLength = ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a. Vector a -> Int
Data.Vector.length (("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int)
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a b. (a -> b) -> a -> b
$ ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes)
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 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
sizesLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
allocationsLength Bool -> Bool -> Bool
|| Int
sizesLength Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== 0) (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 "" "sizes and allocations must have the same length" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
Ptr Allocation
pAllocations <- ((Ptr Allocation -> IO ()) -> IO ())
-> ContT () IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO ()) -> IO ())
-> ContT () IO (Ptr Allocation))
-> ((Ptr Allocation -> IO ()) -> IO ())
-> ContT () IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Allocation -> IO ()) -> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Allocation ((("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length ("allocations" ::: Vector Allocation
allocations)) 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 -> Allocation -> IO ())
-> ("allocations" ::: Vector Allocation) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Allocation
e -> Ptr Allocation -> Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Allocation
pAllocations Ptr Allocation -> Int -> Ptr Allocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Allocation) (Allocation
e)) ("allocations" ::: Vector Allocation
allocations)
Ptr ("lostAllocationCount" ::: Word64)
offsets' <- if ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Bool
forall a. Vector a -> Bool
Data.Vector.null ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets)
then Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr ("lostAllocationCount" ::: Word64)
forall a. Ptr a
nullPtr
else do
Ptr ("lostAllocationCount" ::: Word64)
pOffsets <- ((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64)))
-> ((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr ("lostAllocationCount" ::: Word64) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DeviceSize (((("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets))) 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 -> ("lostAllocationCount" ::: Word64) -> IO ())
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64))
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "lostAllocationCount" ::: Word64
e -> Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lostAllocationCount" ::: Word64)
pOffsets Ptr ("lostAllocationCount" ::: Word64)
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) ("lostAllocationCount" ::: Word64
e)) (("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
offsets))
Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64)))
-> Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall a b. (a -> b) -> a -> b
$ Ptr ("lostAllocationCount" ::: Word64)
pOffsets
Ptr ("lostAllocationCount" ::: Word64)
sizes' <- if ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Bool
forall a. Vector a -> Bool
Data.Vector.null ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes)
then Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr ("lostAllocationCount" ::: Word64)
forall a. Ptr a
nullPtr
else do
Ptr ("lostAllocationCount" ::: Word64)
pSizes <- ((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64)))
-> ((Ptr ("lostAllocationCount" ::: Word64) -> IO ()) -> IO ())
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr ("lostAllocationCount" ::: Word64) -> IO ())
-> IO ()
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @DeviceSize (((("offsets" ::: Vector ("lostAllocationCount" ::: Word64)) -> Int
forall a. Vector a -> Int
Data.Vector.length ("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes))) 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 -> ("lostAllocationCount" ::: Word64) -> IO ())
-> ("offsets" ::: Vector ("lostAllocationCount" ::: Word64))
-> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: "lostAllocationCount" ::: Word64
e -> Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr ("lostAllocationCount" ::: Word64)
pSizes Ptr ("lostAllocationCount" ::: Word64)
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr DeviceSize) ("lostAllocationCount" ::: Word64
e)) (("offsets" ::: Vector ("lostAllocationCount" ::: Word64)
sizes))
Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64)))
-> Ptr ("lostAllocationCount" ::: Word64)
-> ContT () IO (Ptr ("lostAllocationCount" ::: Word64))
forall a b. (a -> b) -> a -> b
$ Ptr ("lostAllocationCount" ::: Word64)
pSizes
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
$ (Allocator
-> ("memoryTypeIndex" ::: Word32)
-> Ptr Allocation
-> Ptr ("lostAllocationCount" ::: Word64)
-> Ptr ("lostAllocationCount" ::: Word64)
-> IO Result
ffiVmaInvalidateAllocations) (Allocator
allocator) ((Int -> "memoryTypeIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
allocationsLength :: Word32)) (Ptr Allocation
pAllocations) Ptr ("lostAllocationCount" ::: Word64)
offsets' Ptr ("lostAllocationCount" ::: Word64)
sizes'
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
"vmaCheckCorruption" ffiVmaCheckCorruption
:: Allocator -> Word32 -> IO Result
checkCorruption :: forall io
. (MonadIO io)
=>
Allocator
->
("memoryTypeBits" ::: Word32)
-> io ()
checkCorruption :: Allocator -> ("memoryTypeIndex" ::: Word32) -> io ()
checkCorruption allocator :: Allocator
allocator memoryTypeBits :: "memoryTypeIndex" ::: Word32
memoryTypeBits = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator -> ("memoryTypeIndex" ::: Word32) -> IO Result
ffiVmaCheckCorruption) (Allocator
allocator) ("memoryTypeIndex" ::: Word32
memoryTypeBits)
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
"vmaDefragmentationBegin" ffiVmaDefragmentationBegin
:: Allocator -> Ptr DefragmentationInfo2 -> Ptr DefragmentationStats -> Ptr DefragmentationContext -> IO Result
defragmentationBegin :: forall io
. (MonadIO io)
=>
Allocator
->
DefragmentationInfo2
-> io (Result, DefragmentationStats, DefragmentationContext)
defragmentationBegin :: Allocator
-> DefragmentationInfo2
-> io (Result, DefragmentationStats, DefragmentationContext)
defragmentationBegin allocator :: Allocator
allocator info :: DefragmentationInfo2
info = IO (Result, DefragmentationStats, DefragmentationContext)
-> io (Result, DefragmentationStats, DefragmentationContext)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Result, DefragmentationStats, DefragmentationContext)
-> io (Result, DefragmentationStats, DefragmentationContext))
-> (ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Result, DefragmentationStats, DefragmentationContext)
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Result, DefragmentationStats, DefragmentationContext)
-> io (Result, DefragmentationStats, DefragmentationContext)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Result, DefragmentationStats, DefragmentationContext)
-> IO (Result, DefragmentationStats, DefragmentationContext)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Result, DefragmentationStats, DefragmentationContext)
-> io (Result, DefragmentationStats, DefragmentationContext))
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Result, DefragmentationStats, DefragmentationContext)
-> io (Result, DefragmentationStats, DefragmentationContext)
forall a b. (a -> b) -> a -> b
$ do
Ptr DefragmentationInfo2
pInfo <- ((Ptr DefragmentationInfo2
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Ptr DefragmentationInfo2)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DefragmentationInfo2
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Ptr DefragmentationInfo2))
-> ((Ptr DefragmentationInfo2
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Ptr DefragmentationInfo2)
forall a b. (a -> b) -> a -> b
$ DefragmentationInfo2
-> (Ptr DefragmentationInfo2
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> IO (Result, DefragmentationStats, DefragmentationContext)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DefragmentationInfo2
info)
Ptr DefragmentationStats
pPStats <- ((Ptr DefragmentationStats
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Ptr DefragmentationStats)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct DefragmentationStats =>
(Ptr DefragmentationStats -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @DefragmentationStats)
Ptr DefragmentationContext
pPContext <- ((Ptr DefragmentationContext
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Ptr DefragmentationContext)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DefragmentationContext
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Ptr DefragmentationContext))
-> ((Ptr DefragmentationContext
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Ptr DefragmentationContext)
forall a b. (a -> b) -> a -> b
$ IO (Ptr DefragmentationContext)
-> (Ptr DefragmentationContext -> IO ())
-> (Ptr DefragmentationContext
-> IO (Result, DefragmentationStats, DefragmentationContext))
-> IO (Result, DefragmentationStats, DefragmentationContext)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr DefragmentationContext)
forall a. Int -> IO (Ptr a)
callocBytes @DefragmentationContext 8) Ptr DefragmentationContext -> IO ()
forall a. Ptr a -> IO ()
free
Result
r <- IO Result
-> ContT
(Result, DefragmentationStats, DefragmentationContext) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
(Result, DefragmentationStats, DefragmentationContext) IO Result)
-> IO Result
-> ContT
(Result, DefragmentationStats, DefragmentationContext) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Ptr DefragmentationInfo2
-> Ptr DefragmentationStats
-> Ptr DefragmentationContext
-> IO Result
ffiVmaDefragmentationBegin) (Allocator
allocator) Ptr DefragmentationInfo2
pInfo (Ptr DefragmentationStats
pPStats) (Ptr DefragmentationContext
pPContext)
IO ()
-> ContT
(Result, DefragmentationStats, DefragmentationContext) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
(Result, DefragmentationStats, DefragmentationContext) IO ())
-> IO ()
-> ContT
(Result, DefragmentationStats, DefragmentationContext) 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))
DefragmentationStats
pStats <- IO DefragmentationStats
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
DefragmentationStats
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO DefragmentationStats
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
DefragmentationStats)
-> IO DefragmentationStats
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
DefragmentationStats
forall a b. (a -> b) -> a -> b
$ Ptr DefragmentationStats -> IO DefragmentationStats
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DefragmentationStats Ptr DefragmentationStats
pPStats
DefragmentationContext
pContext <- IO DefragmentationContext
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
DefragmentationContext
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO DefragmentationContext
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
DefragmentationContext)
-> IO DefragmentationContext
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
DefragmentationContext
forall a b. (a -> b) -> a -> b
$ Ptr DefragmentationContext -> IO DefragmentationContext
forall a. Storable a => Ptr a -> IO a
peek @DefragmentationContext Ptr DefragmentationContext
pPContext
(Result, DefragmentationStats, DefragmentationContext)
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Result, DefragmentationStats, DefragmentationContext)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Result, DefragmentationStats, DefragmentationContext)
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Result, DefragmentationStats, DefragmentationContext))
-> (Result, DefragmentationStats, DefragmentationContext)
-> ContT
(Result, DefragmentationStats, DefragmentationContext)
IO
(Result, DefragmentationStats, DefragmentationContext)
forall a b. (a -> b) -> a -> b
$ (Result
r, DefragmentationStats
pStats, DefragmentationContext
pContext)
withDefragmentation :: forall io r . MonadIO io => Allocator -> DefragmentationInfo2 -> (io (Result, DefragmentationStats, DefragmentationContext) -> ((Result, DefragmentationStats, DefragmentationContext) -> io ()) -> r) -> r
withDefragmentation :: Allocator
-> DefragmentationInfo2
-> (io (Result, DefragmentationStats, DefragmentationContext)
-> ((Result, DefragmentationStats, DefragmentationContext)
-> io ())
-> r)
-> r
withDefragmentation allocator :: Allocator
allocator pInfo :: DefragmentationInfo2
pInfo b :: io (Result, DefragmentationStats, DefragmentationContext)
-> ((Result, DefragmentationStats, DefragmentationContext)
-> io ())
-> r
b =
io (Result, DefragmentationStats, DefragmentationContext)
-> ((Result, DefragmentationStats, DefragmentationContext)
-> io ())
-> r
b (Allocator
-> DefragmentationInfo2
-> io (Result, DefragmentationStats, DefragmentationContext)
forall (io :: * -> *).
MonadIO io =>
Allocator
-> DefragmentationInfo2
-> io (Result, DefragmentationStats, DefragmentationContext)
defragmentationBegin Allocator
allocator DefragmentationInfo2
pInfo)
(\(_, _, o2 :: DefragmentationContext
o2) -> Allocator -> DefragmentationContext -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> DefragmentationContext -> io ()
defragmentationEnd Allocator
allocator DefragmentationContext
o2)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaDefragmentationEnd" ffiVmaDefragmentationEnd
:: Allocator -> DefragmentationContext -> IO Result
defragmentationEnd :: forall io
. (MonadIO io)
=>
Allocator
->
DefragmentationContext
-> io ()
defragmentationEnd :: Allocator -> DefragmentationContext -> io ()
defragmentationEnd allocator :: Allocator
allocator context :: DefragmentationContext
context = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator -> DefragmentationContext -> IO Result
ffiVmaDefragmentationEnd) (Allocator
allocator) (DefragmentationContext
context)
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
"vmaBeginDefragmentationPass" ffiVmaBeginDefragmentationPass
:: Allocator -> DefragmentationContext -> Ptr DefragmentationPassInfo -> IO Result
beginDefragmentationPass :: forall io
. (MonadIO io)
=>
Allocator
->
DefragmentationContext
-> io (DefragmentationPassInfo)
beginDefragmentationPass :: Allocator -> DefragmentationContext -> io DefragmentationPassInfo
beginDefragmentationPass allocator :: Allocator
allocator context :: DefragmentationContext
context = IO DefragmentationPassInfo -> io DefragmentationPassInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DefragmentationPassInfo -> io DefragmentationPassInfo)
-> (ContT DefragmentationPassInfo IO DefragmentationPassInfo
-> IO DefragmentationPassInfo)
-> ContT DefragmentationPassInfo IO DefragmentationPassInfo
-> io DefragmentationPassInfo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT DefragmentationPassInfo IO DefragmentationPassInfo
-> IO DefragmentationPassInfo
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT DefragmentationPassInfo IO DefragmentationPassInfo
-> io DefragmentationPassInfo)
-> ContT DefragmentationPassInfo IO DefragmentationPassInfo
-> io DefragmentationPassInfo
forall a b. (a -> b) -> a -> b
$ do
Ptr DefragmentationPassInfo
pPInfo <- ((Ptr DefragmentationPassInfo -> IO DefragmentationPassInfo)
-> IO DefragmentationPassInfo)
-> ContT DefragmentationPassInfo IO (Ptr DefragmentationPassInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct DefragmentationPassInfo =>
(Ptr DefragmentationPassInfo -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @DefragmentationPassInfo)
Result
r <- IO Result -> ContT DefragmentationPassInfo IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT DefragmentationPassInfo IO Result)
-> IO Result -> ContT DefragmentationPassInfo IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> DefragmentationContext
-> Ptr DefragmentationPassInfo
-> IO Result
ffiVmaBeginDefragmentationPass) (Allocator
allocator) (DefragmentationContext
context) (Ptr DefragmentationPassInfo
pPInfo)
IO () -> ContT DefragmentationPassInfo IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT DefragmentationPassInfo IO ())
-> IO () -> ContT DefragmentationPassInfo 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))
DefragmentationPassInfo
pInfo <- IO DefragmentationPassInfo
-> ContT DefragmentationPassInfo IO DefragmentationPassInfo
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO DefragmentationPassInfo
-> ContT DefragmentationPassInfo IO DefragmentationPassInfo)
-> IO DefragmentationPassInfo
-> ContT DefragmentationPassInfo IO DefragmentationPassInfo
forall a b. (a -> b) -> a -> b
$ Ptr DefragmentationPassInfo -> IO DefragmentationPassInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DefragmentationPassInfo Ptr DefragmentationPassInfo
pPInfo
DefragmentationPassInfo
-> ContT DefragmentationPassInfo IO DefragmentationPassInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DefragmentationPassInfo
-> ContT DefragmentationPassInfo IO DefragmentationPassInfo)
-> DefragmentationPassInfo
-> ContT DefragmentationPassInfo IO DefragmentationPassInfo
forall a b. (a -> b) -> a -> b
$ (DefragmentationPassInfo
pInfo)
useDefragmentationPass :: forall io r . MonadIO io => Allocator -> DefragmentationContext -> ((DefragmentationPassInfo) -> io r) -> io r
useDefragmentationPass :: Allocator
-> DefragmentationContext
-> (DefragmentationPassInfo -> io r)
-> io r
useDefragmentationPass allocator :: Allocator
allocator context :: DefragmentationContext
context a :: DefragmentationPassInfo -> io r
a =
do
DefragmentationPassInfo
x <- Allocator -> DefragmentationContext -> io DefragmentationPassInfo
forall (io :: * -> *).
MonadIO io =>
Allocator -> DefragmentationContext -> io DefragmentationPassInfo
beginDefragmentationPass Allocator
allocator DefragmentationContext
context
r
r <- DefragmentationPassInfo -> io r
a DefragmentationPassInfo
x
(\(DefragmentationPassInfo
_) -> Allocator -> DefragmentationContext -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> DefragmentationContext -> io ()
endDefragmentationPass Allocator
allocator DefragmentationContext
context) DefragmentationPassInfo
x
r -> io r
forall (f :: * -> *) a. Applicative f => a -> f a
pure r
r
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaEndDefragmentationPass" ffiVmaEndDefragmentationPass
:: Allocator -> DefragmentationContext -> IO Result
endDefragmentationPass :: forall io
. (MonadIO io)
=>
Allocator
->
DefragmentationContext
-> io ()
endDefragmentationPass :: Allocator -> DefragmentationContext -> io ()
endDefragmentationPass allocator :: Allocator
allocator context :: DefragmentationContext
context = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator -> DefragmentationContext -> IO Result
ffiVmaEndDefragmentationPass) (Allocator
allocator) (DefragmentationContext
context)
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
"vmaDefragment" ffiVmaDefragment
:: Allocator -> Ptr Allocation -> CSize -> Ptr Bool32 -> Ptr DefragmentationInfo -> Ptr DefragmentationStats -> IO Result
defragment :: forall io
. (MonadIO io)
=>
Allocator
->
("allocations" ::: Vector Allocation)
->
("defragmentationInfo" ::: Maybe DefragmentationInfo)
-> io (("allocationsChanged" ::: Vector Bool), DefragmentationStats)
defragment :: Allocator
-> ("allocations" ::: Vector Allocation)
-> ("defragmentationInfo" ::: Maybe DefragmentationInfo)
-> io ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
defragment allocator :: Allocator
allocator allocations :: "allocations" ::: Vector Allocation
allocations defragmentationInfo :: "defragmentationInfo" ::: Maybe DefragmentationInfo
defragmentationInfo = IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> io ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> io ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> (ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> io ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> io ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> io ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
forall a b. (a -> b) -> a -> b
$ do
Ptr Allocation
pPAllocations <- ((Ptr Allocation
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr Allocation))
-> ((Ptr Allocation
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ Int
-> Int
-> (Ptr Allocation
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Allocation ((("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length ("allocations" ::: Vector Allocation
allocations)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
IO ()
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats) IO ())
-> IO ()
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats) IO ()
forall a b. (a -> b) -> a -> b
$ (Int -> Allocation -> IO ())
-> ("allocations" ::: Vector Allocation) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Allocation
e -> Ptr Allocation -> Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Allocation
pPAllocations Ptr Allocation -> Int -> Ptr Allocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Allocation) (Allocation
e)) ("allocations" ::: Vector Allocation
allocations)
Ptr Bool32
pPAllocationsChanged <- ((Ptr Bool32
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr Bool32)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Bool32
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr Bool32))
-> ((Ptr Bool32
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr Bool32)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Bool32)
-> (Ptr Bool32 -> IO ())
-> (Ptr Bool32
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Bool32)
forall a. Int -> IO (Ptr a)
callocBytes @Bool32 ((CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length (("allocations" ::: Vector Allocation) -> Int)
-> ("allocations" ::: Vector Allocation) -> Int
forall a b. (a -> b) -> a -> b
$ ("allocations" ::: Vector Allocation
allocations)) :: CSize))) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 4)) Ptr Bool32 -> IO ()
forall a. Ptr a -> IO ()
free
Ptr DefragmentationInfo
pDefragmentationInfo <- case ("defragmentationInfo" ::: Maybe DefragmentationInfo
defragmentationInfo) of
Nothing -> Ptr DefragmentationInfo
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr DefragmentationInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr DefragmentationInfo
forall a. Ptr a
nullPtr
Just j :: DefragmentationInfo
j -> ((Ptr DefragmentationInfo
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr DefragmentationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DefragmentationInfo
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr DefragmentationInfo))
-> ((Ptr DefragmentationInfo
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr DefragmentationInfo)
forall a b. (a -> b) -> a -> b
$ DefragmentationInfo
-> (Ptr DefragmentationInfo
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DefragmentationInfo
j)
Ptr DefragmentationStats
pPDefragmentationStats <- ((Ptr DefragmentationStats
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> IO ("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
(Ptr DefragmentationStats)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct DefragmentationStats =>
(Ptr DefragmentationStats -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @DefragmentationStats)
Result
r <- IO Result
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
Result)
-> IO Result
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Ptr Allocation
-> CSize
-> Ptr Bool32
-> Ptr DefragmentationInfo
-> Ptr DefragmentationStats
-> IO Result
ffiVmaDefragment) (Allocator
allocator) (Ptr Allocation
pPAllocations) ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length (("allocations" ::: Vector Allocation) -> Int)
-> ("allocations" ::: Vector Allocation) -> Int
forall a b. (a -> b) -> a -> b
$ ("allocations" ::: Vector Allocation
allocations)) :: CSize)) (Ptr Bool32
pPAllocationsChanged) Ptr DefragmentationInfo
pDefragmentationInfo (Ptr DefragmentationStats
pPDefragmentationStats)
IO ()
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ()
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats) IO ())
-> IO ()
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats) 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))
"allocationsChanged" ::: Vector Bool
pAllocationsChanged <- IO ("allocationsChanged" ::: Vector Bool)
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool)
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO ("allocationsChanged" ::: Vector Bool)
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool))
-> IO ("allocationsChanged" ::: Vector Bool)
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool)
forall a b. (a -> b) -> a -> b
$ Int
-> (Int -> IO Bool) -> IO ("allocationsChanged" ::: Vector Bool)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral ((Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length (("allocations" ::: Vector Allocation) -> Int)
-> ("allocations" ::: Vector Allocation) -> Int
forall a b. (a -> b) -> a -> b
$ ("allocations" ::: Vector Allocation
allocations)) :: CSize))) (\i :: Int
i -> do
Bool32
pAllocationsChangedElem <- Ptr Bool32 -> IO Bool32
forall a. Storable a => Ptr a -> IO a
peek @Bool32 ((Ptr Bool32
pPAllocationsChanged Ptr Bool32 -> Int -> Ptr Bool32
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (4 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Bool32))
Bool -> IO Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Bool32 -> Bool
bool32ToBool Bool32
pAllocationsChangedElem)
DefragmentationStats
pDefragmentationStats <- IO DefragmentationStats
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
DefragmentationStats
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO DefragmentationStats
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
DefragmentationStats)
-> IO DefragmentationStats
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
DefragmentationStats
forall a b. (a -> b) -> a -> b
$ Ptr DefragmentationStats -> IO DefragmentationStats
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DefragmentationStats Ptr DefragmentationStats
pPDefragmentationStats
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool, DefragmentationStats))
-> ("allocationsChanged" ::: Vector Bool, DefragmentationStats)
-> ContT
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
IO
("allocationsChanged" ::: Vector Bool, DefragmentationStats)
forall a b. (a -> b) -> a -> b
$ ("allocationsChanged" ::: Vector Bool
pAllocationsChanged, DefragmentationStats
pDefragmentationStats)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaBindBufferMemory" ffiVmaBindBufferMemory
:: Allocator -> Allocation -> Buffer -> IO Result
bindBufferMemory :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
->
Buffer
-> io ()
bindBufferMemory :: Allocator -> Allocation -> Buffer -> io ()
bindBufferMemory allocator :: Allocator
allocator allocation :: Allocation
allocation buffer :: Buffer
buffer = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator -> Allocation -> Buffer -> IO Result
ffiVmaBindBufferMemory) (Allocator
allocator) (Allocation
allocation) (Buffer
buffer)
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
"vmaBindBufferMemory2" ffiVmaBindBufferMemory2
:: Allocator -> Allocation -> DeviceSize -> Buffer -> Ptr () -> IO Result
bindBufferMemory2 :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
->
("allocationLocalOffset" ::: DeviceSize)
->
Buffer
->
("next" ::: Ptr ())
-> io ()
bindBufferMemory2 :: Allocator
-> Allocation
-> ("lostAllocationCount" ::: Word64)
-> Buffer
-> ("userData" ::: Ptr ())
-> io ()
bindBufferMemory2 allocator :: Allocator
allocator allocation :: Allocation
allocation allocationLocalOffset :: "lostAllocationCount" ::: Word64
allocationLocalOffset buffer :: Buffer
buffer next :: "userData" ::: Ptr ()
next = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator
-> Allocation
-> ("lostAllocationCount" ::: Word64)
-> Buffer
-> ("userData" ::: Ptr ())
-> IO Result
ffiVmaBindBufferMemory2) (Allocator
allocator) (Allocation
allocation) ("lostAllocationCount" ::: Word64
allocationLocalOffset) (Buffer
buffer) ("userData" ::: Ptr ()
next)
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
"vmaBindImageMemory" ffiVmaBindImageMemory
:: Allocator -> Allocation -> Image -> IO Result
bindImageMemory :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
->
Image
-> io ()
bindImageMemory :: Allocator -> Allocation -> Image -> io ()
bindImageMemory allocator :: Allocator
allocator allocation :: Allocation
allocation image :: Image
image = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator -> Allocation -> Image -> IO Result
ffiVmaBindImageMemory) (Allocator
allocator) (Allocation
allocation) (Image
image)
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
"vmaBindImageMemory2" ffiVmaBindImageMemory2
:: Allocator -> Allocation -> DeviceSize -> Image -> Ptr () -> IO Result
bindImageMemory2 :: forall io
. (MonadIO io)
=>
Allocator
->
Allocation
->
("allocationLocalOffset" ::: DeviceSize)
->
Image
->
("next" ::: Ptr ())
-> io ()
bindImageMemory2 :: Allocator
-> Allocation
-> ("lostAllocationCount" ::: Word64)
-> Image
-> ("userData" ::: Ptr ())
-> io ()
bindImageMemory2 allocator :: Allocator
allocator allocation :: Allocation
allocation allocationLocalOffset :: "lostAllocationCount" ::: Word64
allocationLocalOffset image :: Image
image next :: "userData" ::: Ptr ()
next = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
Result
r <- (Allocator
-> Allocation
-> ("lostAllocationCount" ::: Word64)
-> Image
-> ("userData" ::: Ptr ())
-> IO Result
ffiVmaBindImageMemory2) (Allocator
allocator) (Allocation
allocation) ("lostAllocationCount" ::: Word64
allocationLocalOffset) (Image
image) ("userData" ::: Ptr ()
next)
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
"vmaCreateBuffer" ffiVmaCreateBuffer
:: Allocator -> Ptr (SomeStruct BufferCreateInfo) -> Ptr AllocationCreateInfo -> Ptr Buffer -> Ptr Allocation -> Ptr AllocationInfo -> IO Result
createBuffer :: forall a io
. (Extendss BufferCreateInfo a, PokeChain a, MonadIO io)
=>
Allocator
->
(BufferCreateInfo a)
->
AllocationCreateInfo
-> io (Buffer, Allocation, AllocationInfo)
createBuffer :: Allocator
-> BufferCreateInfo a
-> AllocationCreateInfo
-> io (Buffer, Allocation, AllocationInfo)
createBuffer allocator :: Allocator
allocator bufferCreateInfo :: BufferCreateInfo a
bufferCreateInfo allocationCreateInfo :: AllocationCreateInfo
allocationCreateInfo = IO (Buffer, Allocation, AllocationInfo)
-> io (Buffer, Allocation, AllocationInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Buffer, Allocation, AllocationInfo)
-> io (Buffer, Allocation, AllocationInfo))
-> (ContT
(Buffer, Allocation, AllocationInfo)
IO
(Buffer, Allocation, AllocationInfo)
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT
(Buffer, Allocation, AllocationInfo)
IO
(Buffer, Allocation, AllocationInfo)
-> io (Buffer, Allocation, AllocationInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
(Buffer, Allocation, AllocationInfo)
IO
(Buffer, Allocation, AllocationInfo)
-> IO (Buffer, Allocation, AllocationInfo)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
(Buffer, Allocation, AllocationInfo)
IO
(Buffer, Allocation, AllocationInfo)
-> io (Buffer, Allocation, AllocationInfo))
-> ContT
(Buffer, Allocation, AllocationInfo)
IO
(Buffer, Allocation, AllocationInfo)
-> io (Buffer, Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ do
Ptr (BufferCreateInfo a)
pBufferCreateInfo <- ((Ptr (BufferCreateInfo a)
-> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT
(Buffer, Allocation, AllocationInfo) IO (Ptr (BufferCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (BufferCreateInfo a)
-> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT
(Buffer, Allocation, AllocationInfo) IO (Ptr (BufferCreateInfo a)))
-> ((Ptr (BufferCreateInfo a)
-> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT
(Buffer, Allocation, AllocationInfo) IO (Ptr (BufferCreateInfo a))
forall a b. (a -> b) -> a -> b
$ BufferCreateInfo a
-> (Ptr (BufferCreateInfo a)
-> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (BufferCreateInfo a
bufferCreateInfo)
Ptr AllocationCreateInfo
pAllocationCreateInfo <- ((Ptr AllocationCreateInfo
-> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT
(Buffer, Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCreateInfo
-> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT
(Buffer, Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo))
-> ((Ptr AllocationCreateInfo
-> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT
(Buffer, Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall a b. (a -> b) -> a -> b
$ AllocationCreateInfo
-> (Ptr AllocationCreateInfo
-> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCreateInfo
allocationCreateInfo)
Ptr Buffer
pPBuffer <- ((Ptr Buffer -> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT (Buffer, Allocation, AllocationInfo) IO (Ptr Buffer)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Buffer -> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT (Buffer, Allocation, AllocationInfo) IO (Ptr Buffer))
-> ((Ptr Buffer -> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT (Buffer, Allocation, AllocationInfo) IO (Ptr Buffer)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Buffer)
-> (Ptr Buffer -> IO ())
-> (Ptr Buffer -> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Buffer)
forall a. Int -> IO (Ptr a)
callocBytes @Buffer 8) Ptr Buffer -> IO ()
forall a. Ptr a -> IO ()
free
Ptr Allocation
pPAllocation <- ((Ptr Allocation -> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT (Buffer, Allocation, AllocationInfo) IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT (Buffer, Allocation, AllocationInfo) IO (Ptr Allocation))
-> ((Ptr Allocation -> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT (Buffer, Allocation, AllocationInfo) IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Allocation)
-> (Ptr Allocation -> IO ())
-> (Ptr Allocation -> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Allocation)
forall a. Int -> IO (Ptr a)
callocBytes @Allocation 8) Ptr Allocation -> IO ()
forall a. Ptr a -> IO ()
free
Ptr AllocationInfo
pPAllocationInfo <- ((Ptr AllocationInfo -> IO (Buffer, Allocation, AllocationInfo))
-> IO (Buffer, Allocation, AllocationInfo))
-> ContT
(Buffer, Allocation, AllocationInfo) IO (Ptr AllocationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct AllocationInfo =>
(Ptr AllocationInfo -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @AllocationInfo)
Result
r <- IO Result -> ContT (Buffer, Allocation, AllocationInfo) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Buffer, Allocation, AllocationInfo) IO Result)
-> IO Result
-> ContT (Buffer, Allocation, AllocationInfo) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Ptr (SomeStruct BufferCreateInfo)
-> Ptr AllocationCreateInfo
-> Ptr Buffer
-> Ptr Allocation
-> Ptr AllocationInfo
-> IO Result
ffiVmaCreateBuffer) (Allocator
allocator) (Ptr (BufferCreateInfo a) -> Ptr (SomeStruct BufferCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (BufferCreateInfo a)
pBufferCreateInfo) Ptr AllocationCreateInfo
pAllocationCreateInfo (Ptr Buffer
pPBuffer) (Ptr Allocation
pPAllocation) (Ptr AllocationInfo
pPAllocationInfo)
IO () -> ContT (Buffer, Allocation, AllocationInfo) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Buffer, Allocation, AllocationInfo) IO ())
-> IO () -> ContT (Buffer, Allocation, AllocationInfo) 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))
Buffer
pBuffer <- IO Buffer -> ContT (Buffer, Allocation, AllocationInfo) IO Buffer
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Buffer -> ContT (Buffer, Allocation, AllocationInfo) IO Buffer)
-> IO Buffer
-> ContT (Buffer, Allocation, AllocationInfo) IO Buffer
forall a b. (a -> b) -> a -> b
$ Ptr Buffer -> IO Buffer
forall a. Storable a => Ptr a -> IO a
peek @Buffer Ptr Buffer
pPBuffer
Allocation
pAllocation <- IO Allocation
-> ContT (Buffer, Allocation, AllocationInfo) IO Allocation
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Allocation
-> ContT (Buffer, Allocation, AllocationInfo) IO Allocation)
-> IO Allocation
-> ContT (Buffer, Allocation, AllocationInfo) IO Allocation
forall a b. (a -> b) -> a -> b
$ Ptr Allocation -> IO Allocation
forall a. Storable a => Ptr a -> IO a
peek @Allocation Ptr Allocation
pPAllocation
AllocationInfo
pAllocationInfo <- IO AllocationInfo
-> ContT (Buffer, Allocation, AllocationInfo) IO AllocationInfo
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO AllocationInfo
-> ContT (Buffer, Allocation, AllocationInfo) IO AllocationInfo)
-> IO AllocationInfo
-> ContT (Buffer, Allocation, AllocationInfo) IO AllocationInfo
forall a b. (a -> b) -> a -> b
$ Ptr AllocationInfo -> IO AllocationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AllocationInfo Ptr AllocationInfo
pPAllocationInfo
(Buffer, Allocation, AllocationInfo)
-> ContT
(Buffer, Allocation, AllocationInfo)
IO
(Buffer, Allocation, AllocationInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Buffer, Allocation, AllocationInfo)
-> ContT
(Buffer, Allocation, AllocationInfo)
IO
(Buffer, Allocation, AllocationInfo))
-> (Buffer, Allocation, AllocationInfo)
-> ContT
(Buffer, Allocation, AllocationInfo)
IO
(Buffer, Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ (Buffer
pBuffer, Allocation
pAllocation, AllocationInfo
pAllocationInfo)
withBuffer :: forall a io r . (Extendss BufferCreateInfo a, PokeChain a, MonadIO io) => Allocator -> BufferCreateInfo a -> AllocationCreateInfo -> (io (Buffer, Allocation, AllocationInfo) -> ((Buffer, Allocation, AllocationInfo) -> io ()) -> r) -> r
withBuffer :: Allocator
-> BufferCreateInfo a
-> AllocationCreateInfo
-> (io (Buffer, Allocation, AllocationInfo)
-> ((Buffer, Allocation, AllocationInfo) -> io ()) -> r)
-> r
withBuffer allocator :: Allocator
allocator pBufferCreateInfo :: BufferCreateInfo a
pBufferCreateInfo pAllocationCreateInfo :: AllocationCreateInfo
pAllocationCreateInfo b :: io (Buffer, Allocation, AllocationInfo)
-> ((Buffer, Allocation, AllocationInfo) -> io ()) -> r
b =
io (Buffer, Allocation, AllocationInfo)
-> ((Buffer, Allocation, AllocationInfo) -> io ()) -> r
b (Allocator
-> BufferCreateInfo a
-> AllocationCreateInfo
-> io (Buffer, Allocation, AllocationInfo)
forall (a :: [*]) (io :: * -> *).
(Extendss BufferCreateInfo a, PokeChain a, MonadIO io) =>
Allocator
-> BufferCreateInfo a
-> AllocationCreateInfo
-> io (Buffer, Allocation, AllocationInfo)
createBuffer Allocator
allocator BufferCreateInfo a
pBufferCreateInfo AllocationCreateInfo
pAllocationCreateInfo)
(\(o0 :: Buffer
o0, o1 :: Allocation
o1, _) -> Allocator -> Buffer -> Allocation -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> Buffer -> Allocation -> io ()
destroyBuffer Allocator
allocator Buffer
o0 Allocation
o1)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaDestroyBuffer" ffiVmaDestroyBuffer
:: Allocator -> Buffer -> Allocation -> IO ()
destroyBuffer :: forall io
. (MonadIO io)
=>
Allocator
->
Buffer
->
Allocation
-> io ()
destroyBuffer :: Allocator -> Buffer -> Allocation -> io ()
destroyBuffer allocator :: Allocator
allocator buffer :: Buffer
buffer allocation :: Allocation
allocation = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
(Allocator -> Buffer -> Allocation -> IO ()
ffiVmaDestroyBuffer) (Allocator
allocator) (Buffer
buffer) (Allocation
allocation)
() -> 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
"vmaCreateImage" ffiVmaCreateImage
:: Allocator -> Ptr (SomeStruct ImageCreateInfo) -> Ptr AllocationCreateInfo -> Ptr Image -> Ptr Allocation -> Ptr AllocationInfo -> IO Result
createImage :: forall a io
. (Extendss ImageCreateInfo a, PokeChain a, MonadIO io)
=>
Allocator
->
(ImageCreateInfo a)
->
AllocationCreateInfo
-> io (Image, Allocation, AllocationInfo)
createImage :: Allocator
-> ImageCreateInfo a
-> AllocationCreateInfo
-> io (Image, Allocation, AllocationInfo)
createImage allocator :: Allocator
allocator imageCreateInfo :: ImageCreateInfo a
imageCreateInfo allocationCreateInfo :: AllocationCreateInfo
allocationCreateInfo = IO (Image, Allocation, AllocationInfo)
-> io (Image, Allocation, AllocationInfo)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Image, Allocation, AllocationInfo)
-> io (Image, Allocation, AllocationInfo))
-> (ContT
(Image, Allocation, AllocationInfo)
IO
(Image, Allocation, AllocationInfo)
-> IO (Image, Allocation, AllocationInfo))
-> ContT
(Image, Allocation, AllocationInfo)
IO
(Image, Allocation, AllocationInfo)
-> io (Image, Allocation, AllocationInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ContT
(Image, Allocation, AllocationInfo)
IO
(Image, Allocation, AllocationInfo)
-> IO (Image, Allocation, AllocationInfo)
forall (m :: * -> *) r. Monad m => ContT r m r -> m r
evalContT (ContT
(Image, Allocation, AllocationInfo)
IO
(Image, Allocation, AllocationInfo)
-> io (Image, Allocation, AllocationInfo))
-> ContT
(Image, Allocation, AllocationInfo)
IO
(Image, Allocation, AllocationInfo)
-> io (Image, Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ do
Ptr (ImageCreateInfo a)
pImageCreateInfo <- ((Ptr (ImageCreateInfo a)
-> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT
(Image, Allocation, AllocationInfo) IO (Ptr (ImageCreateInfo a))
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr (ImageCreateInfo a)
-> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT
(Image, Allocation, AllocationInfo) IO (Ptr (ImageCreateInfo a)))
-> ((Ptr (ImageCreateInfo a)
-> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT
(Image, Allocation, AllocationInfo) IO (Ptr (ImageCreateInfo a))
forall a b. (a -> b) -> a -> b
$ ImageCreateInfo a
-> (Ptr (ImageCreateInfo a)
-> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (ImageCreateInfo a
imageCreateInfo)
Ptr AllocationCreateInfo
pAllocationCreateInfo <- ((Ptr AllocationCreateInfo
-> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT
(Image, Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCreateInfo
-> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT
(Image, Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo))
-> ((Ptr AllocationCreateInfo
-> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT
(Image, Allocation, AllocationInfo) IO (Ptr AllocationCreateInfo)
forall a b. (a -> b) -> a -> b
$ AllocationCreateInfo
-> (Ptr AllocationCreateInfo
-> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo)
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCreateInfo
allocationCreateInfo)
Ptr Image
pPImage <- ((Ptr Image -> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT (Image, Allocation, AllocationInfo) IO (Ptr Image)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Image -> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT (Image, Allocation, AllocationInfo) IO (Ptr Image))
-> ((Ptr Image -> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT (Image, Allocation, AllocationInfo) IO (Ptr Image)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Image)
-> (Ptr Image -> IO ())
-> (Ptr Image -> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Image)
forall a. Int -> IO (Ptr a)
callocBytes @Image 8) Ptr Image -> IO ()
forall a. Ptr a -> IO ()
free
Ptr Allocation
pPAllocation <- ((Ptr Allocation -> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT (Image, Allocation, AllocationInfo) IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT (Image, Allocation, AllocationInfo) IO (Ptr Allocation))
-> ((Ptr Allocation -> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT (Image, Allocation, AllocationInfo) IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ IO (Ptr Allocation)
-> (Ptr Allocation -> IO ())
-> (Ptr Allocation -> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo)
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracket (Int -> IO (Ptr Allocation)
forall a. Int -> IO (Ptr a)
callocBytes @Allocation 8) Ptr Allocation -> IO ()
forall a. Ptr a -> IO ()
free
Ptr AllocationInfo
pPAllocationInfo <- ((Ptr AllocationInfo -> IO (Image, Allocation, AllocationInfo))
-> IO (Image, Allocation, AllocationInfo))
-> ContT
(Image, Allocation, AllocationInfo) IO (Ptr AllocationInfo)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (forall b.
ToCStruct AllocationInfo =>
(Ptr AllocationInfo -> IO b) -> IO b
forall a b. ToCStruct a => (Ptr a -> IO b) -> IO b
withZeroCStruct @AllocationInfo)
Result
r <- IO Result -> ContT (Image, Allocation, AllocationInfo) IO Result
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Result -> ContT (Image, Allocation, AllocationInfo) IO Result)
-> IO Result -> ContT (Image, Allocation, AllocationInfo) IO Result
forall a b. (a -> b) -> a -> b
$ (Allocator
-> Ptr (SomeStruct ImageCreateInfo)
-> Ptr AllocationCreateInfo
-> Ptr Image
-> Ptr Allocation
-> Ptr AllocationInfo
-> IO Result
ffiVmaCreateImage) (Allocator
allocator) (Ptr (ImageCreateInfo a) -> Ptr (SomeStruct ImageCreateInfo)
forall (a :: [*] -> *) (es :: [*]).
Ptr (a es) -> Ptr (SomeStruct a)
forgetExtensions Ptr (ImageCreateInfo a)
pImageCreateInfo) Ptr AllocationCreateInfo
pAllocationCreateInfo (Ptr Image
pPImage) (Ptr Allocation
pPAllocation) (Ptr AllocationInfo
pPAllocationInfo)
IO () -> ContT (Image, Allocation, AllocationInfo) IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT (Image, Allocation, AllocationInfo) IO ())
-> IO () -> ContT (Image, Allocation, AllocationInfo) 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))
Image
pImage <- IO Image -> ContT (Image, Allocation, AllocationInfo) IO Image
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Image -> ContT (Image, Allocation, AllocationInfo) IO Image)
-> IO Image -> ContT (Image, Allocation, AllocationInfo) IO Image
forall a b. (a -> b) -> a -> b
$ Ptr Image -> IO Image
forall a. Storable a => Ptr a -> IO a
peek @Image Ptr Image
pPImage
Allocation
pAllocation <- IO Allocation
-> ContT (Image, Allocation, AllocationInfo) IO Allocation
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO Allocation
-> ContT (Image, Allocation, AllocationInfo) IO Allocation)
-> IO Allocation
-> ContT (Image, Allocation, AllocationInfo) IO Allocation
forall a b. (a -> b) -> a -> b
$ Ptr Allocation -> IO Allocation
forall a. Storable a => Ptr a -> IO a
peek @Allocation Ptr Allocation
pPAllocation
AllocationInfo
pAllocationInfo <- IO AllocationInfo
-> ContT (Image, Allocation, AllocationInfo) IO AllocationInfo
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO AllocationInfo
-> ContT (Image, Allocation, AllocationInfo) IO AllocationInfo)
-> IO AllocationInfo
-> ContT (Image, Allocation, AllocationInfo) IO AllocationInfo
forall a b. (a -> b) -> a -> b
$ Ptr AllocationInfo -> IO AllocationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AllocationInfo Ptr AllocationInfo
pPAllocationInfo
(Image, Allocation, AllocationInfo)
-> ContT
(Image, Allocation, AllocationInfo)
IO
(Image, Allocation, AllocationInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((Image, Allocation, AllocationInfo)
-> ContT
(Image, Allocation, AllocationInfo)
IO
(Image, Allocation, AllocationInfo))
-> (Image, Allocation, AllocationInfo)
-> ContT
(Image, Allocation, AllocationInfo)
IO
(Image, Allocation, AllocationInfo)
forall a b. (a -> b) -> a -> b
$ (Image
pImage, Allocation
pAllocation, AllocationInfo
pAllocationInfo)
withImage :: forall a io r . (Extendss ImageCreateInfo a, PokeChain a, MonadIO io) => Allocator -> ImageCreateInfo a -> AllocationCreateInfo -> (io (Image, Allocation, AllocationInfo) -> ((Image, Allocation, AllocationInfo) -> io ()) -> r) -> r
withImage :: Allocator
-> ImageCreateInfo a
-> AllocationCreateInfo
-> (io (Image, Allocation, AllocationInfo)
-> ((Image, Allocation, AllocationInfo) -> io ()) -> r)
-> r
withImage allocator :: Allocator
allocator pImageCreateInfo :: ImageCreateInfo a
pImageCreateInfo pAllocationCreateInfo :: AllocationCreateInfo
pAllocationCreateInfo b :: io (Image, Allocation, AllocationInfo)
-> ((Image, Allocation, AllocationInfo) -> io ()) -> r
b =
io (Image, Allocation, AllocationInfo)
-> ((Image, Allocation, AllocationInfo) -> io ()) -> r
b (Allocator
-> ImageCreateInfo a
-> AllocationCreateInfo
-> io (Image, Allocation, AllocationInfo)
forall (a :: [*]) (io :: * -> *).
(Extendss ImageCreateInfo a, PokeChain a, MonadIO io) =>
Allocator
-> ImageCreateInfo a
-> AllocationCreateInfo
-> io (Image, Allocation, AllocationInfo)
createImage Allocator
allocator ImageCreateInfo a
pImageCreateInfo AllocationCreateInfo
pAllocationCreateInfo)
(\(o0 :: Image
o0, o1 :: Allocation
o1, _) -> Allocator -> Image -> Allocation -> io ()
forall (io :: * -> *).
MonadIO io =>
Allocator -> Image -> Allocation -> io ()
destroyImage Allocator
allocator Image
o0 Allocation
o1)
foreign import ccall
#if !defined(SAFE_FOREIGN_CALLS)
unsafe
#endif
"vmaDestroyImage" ffiVmaDestroyImage
:: Allocator -> Image -> Allocation -> IO ()
destroyImage :: forall io
. (MonadIO io)
=>
Allocator
->
Image
->
Allocation
-> io ()
destroyImage :: Allocator -> Image -> Allocation -> io ()
destroyImage allocator :: Allocator
allocator image :: Image
image allocation :: Allocation
allocation = IO () -> io ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> io ()) -> IO () -> io ()
forall a b. (a -> b) -> a -> b
$ do
(Allocator -> Image -> Allocation -> IO ()
ffiVmaDestroyImage) (Allocator
allocator) (Image
image) (Allocation
allocation)
() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> IO ()) -> () -> IO ()
forall a b. (a -> b) -> a -> b
$ ()
type FN_vkAllocateMemory = Ptr Device_T -> ("pAllocateInfo" ::: Ptr (SomeStruct MemoryAllocateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pMemory" ::: Ptr DeviceMemory) -> IO Result
type PFN_vkAllocateMemory = FunPtr FN_vkAllocateMemory
type FN_vkBindBufferMemory = Ptr Device_T -> Buffer -> DeviceMemory -> ("memoryOffset" ::: DeviceSize) -> IO Result
type PFN_vkBindBufferMemory = FunPtr FN_vkBindBufferMemory
type FN_vkBindBufferMemory2KHR = Ptr Device_T -> ("bindInfoCount" ::: Word32) -> ("pBindInfos" ::: Ptr (SomeStruct BindBufferMemoryInfo)) -> IO Result
type PFN_vkBindBufferMemory2KHR = FunPtr FN_vkBindBufferMemory2KHR
type FN_vkBindImageMemory = Ptr Device_T -> Image -> DeviceMemory -> ("memoryOffset" ::: DeviceSize) -> IO Result
type PFN_vkBindImageMemory = FunPtr FN_vkBindImageMemory
type FN_vkBindImageMemory2KHR = Ptr Device_T -> ("bindInfoCount" ::: Word32) -> ("pBindInfos" ::: Ptr (SomeStruct BindImageMemoryInfo)) -> IO Result
type PFN_vkBindImageMemory2KHR = FunPtr FN_vkBindImageMemory2KHR
type FN_vkCmdCopyBuffer = Ptr CommandBuffer_T -> ("srcBuffer" ::: Buffer) -> ("dstBuffer" ::: Buffer) -> ("regionCount" ::: Word32) -> ("pRegions" ::: Ptr BufferCopy) -> IO ()
type PFN_vkCmdCopyBuffer = FunPtr FN_vkCmdCopyBuffer
type FN_vkCreateBuffer = Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct BufferCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pBuffer" ::: Ptr Buffer) -> IO Result
type PFN_vkCreateBuffer = FunPtr FN_vkCreateBuffer
type FN_vkCreateImage = Ptr Device_T -> ("pCreateInfo" ::: Ptr (SomeStruct ImageCreateInfo)) -> ("pAllocator" ::: Ptr AllocationCallbacks) -> ("pImage" ::: Ptr Image) -> IO Result
type PFN_vkCreateImage = FunPtr FN_vkCreateImage
type FN_vkDestroyBuffer = Ptr Device_T -> Buffer -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
type PFN_vkDestroyBuffer = FunPtr FN_vkDestroyBuffer
type FN_vkDestroyImage = Ptr Device_T -> Image -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
type PFN_vkDestroyImage = FunPtr FN_vkDestroyImage
type FN_vkFlushMappedMemoryRanges = Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result
type PFN_vkFlushMappedMemoryRanges = FunPtr FN_vkFlushMappedMemoryRanges
type FN_vkFreeMemory = Ptr Device_T -> DeviceMemory -> ("pAllocator" ::: Ptr AllocationCallbacks) -> IO ()
type PFN_vkFreeMemory = FunPtr FN_vkFreeMemory
type FN_vkGetBufferMemoryRequirements = Ptr Device_T -> Buffer -> ("pMemoryRequirements" ::: Ptr MemoryRequirements) -> IO ()
type PFN_vkGetBufferMemoryRequirements = FunPtr FN_vkGetBufferMemoryRequirements
type FN_vkGetBufferMemoryRequirements2KHR = Ptr Device_T -> ("pInfo" ::: Ptr BufferMemoryRequirementsInfo2) -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2)) -> IO ()
type PFN_vkGetBufferMemoryRequirements2KHR = FunPtr FN_vkGetBufferMemoryRequirements2KHR
type FN_vkGetImageMemoryRequirements = Ptr Device_T -> Image -> ("pMemoryRequirements" ::: Ptr MemoryRequirements) -> IO ()
type PFN_vkGetImageMemoryRequirements = FunPtr FN_vkGetImageMemoryRequirements
type FN_vkGetImageMemoryRequirements2KHR = Ptr Device_T -> ("pInfo" ::: Ptr (SomeStruct ImageMemoryRequirementsInfo2)) -> ("pMemoryRequirements" ::: Ptr (SomeStruct MemoryRequirements2)) -> IO ()
type PFN_vkGetImageMemoryRequirements2KHR = FunPtr FN_vkGetImageMemoryRequirements2KHR
type FN_vkGetPhysicalDeviceMemoryProperties = Ptr PhysicalDevice_T -> ("pMemoryProperties" ::: Ptr PhysicalDeviceMemoryProperties) -> IO ()
type PFN_vkGetPhysicalDeviceMemoryProperties = FunPtr FN_vkGetPhysicalDeviceMemoryProperties
type FN_vkGetPhysicalDeviceMemoryProperties2KHR = Ptr PhysicalDevice_T -> ("pMemoryProperties" ::: Ptr (SomeStruct PhysicalDeviceMemoryProperties2)) -> IO ()
type PFN_vkGetPhysicalDeviceMemoryProperties2KHR = FunPtr FN_vkGetPhysicalDeviceMemoryProperties2KHR
type FN_vkGetPhysicalDeviceProperties = Ptr PhysicalDevice_T -> ("pProperties" ::: Ptr PhysicalDeviceProperties) -> IO ()
type PFN_vkGetPhysicalDeviceProperties = FunPtr FN_vkGetPhysicalDeviceProperties
type FN_vkInvalidateMappedMemoryRanges = Ptr Device_T -> ("memoryRangeCount" ::: Word32) -> ("pMemoryRanges" ::: Ptr MappedMemoryRange) -> IO Result
type PFN_vkInvalidateMappedMemoryRanges = FunPtr FN_vkInvalidateMappedMemoryRanges
type FN_vkMapMemory = Ptr Device_T -> DeviceMemory -> ("offset" ::: DeviceSize) -> DeviceSize -> MemoryMapFlags -> ("ppData" ::: Ptr (Ptr ())) -> IO Result
type PFN_vkMapMemory = FunPtr FN_vkMapMemory
type FN_vkUnmapMemory = Ptr Device_T -> DeviceMemory -> IO ()
type PFN_vkUnmapMemory = FunPtr FN_vkUnmapMemory
newtype Allocator = Allocator Word64
deriving newtype (Allocator -> Allocator -> Bool
(Allocator -> Allocator -> Bool)
-> (Allocator -> Allocator -> Bool) -> Eq Allocator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Allocator -> Allocator -> Bool
$c/= :: Allocator -> Allocator -> Bool
== :: Allocator -> Allocator -> Bool
$c== :: Allocator -> Allocator -> Bool
Eq, Eq Allocator
Eq Allocator =>
(Allocator -> Allocator -> Ordering)
-> (Allocator -> Allocator -> Bool)
-> (Allocator -> Allocator -> Bool)
-> (Allocator -> Allocator -> Bool)
-> (Allocator -> Allocator -> Bool)
-> (Allocator -> Allocator -> Allocator)
-> (Allocator -> Allocator -> Allocator)
-> Ord Allocator
Allocator -> Allocator -> Bool
Allocator -> Allocator -> Ordering
Allocator -> Allocator -> Allocator
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Allocator -> Allocator -> Allocator
$cmin :: Allocator -> Allocator -> Allocator
max :: Allocator -> Allocator -> Allocator
$cmax :: Allocator -> Allocator -> Allocator
>= :: Allocator -> Allocator -> Bool
$c>= :: Allocator -> Allocator -> Bool
> :: Allocator -> Allocator -> Bool
$c> :: Allocator -> Allocator -> Bool
<= :: Allocator -> Allocator -> Bool
$c<= :: Allocator -> Allocator -> Bool
< :: Allocator -> Allocator -> Bool
$c< :: Allocator -> Allocator -> Bool
compare :: Allocator -> Allocator -> Ordering
$ccompare :: Allocator -> Allocator -> Ordering
$cp1Ord :: Eq Allocator
Ord, Ptr b -> Int -> IO Allocator
Ptr b -> Int -> Allocator -> IO ()
Ptr Allocator -> IO Allocator
Ptr Allocator -> Int -> IO Allocator
Ptr Allocator -> Int -> Allocator -> IO ()
Ptr Allocator -> Allocator -> IO ()
Allocator -> Int
(Allocator -> Int)
-> (Allocator -> Int)
-> (Ptr Allocator -> Int -> IO Allocator)
-> (Ptr Allocator -> Int -> Allocator -> IO ())
-> (forall b. Ptr b -> Int -> IO Allocator)
-> (forall b. Ptr b -> Int -> Allocator -> IO ())
-> (Ptr Allocator -> IO Allocator)
-> (Ptr Allocator -> Allocator -> IO ())
-> Storable Allocator
forall b. Ptr b -> Int -> IO Allocator
forall b. Ptr b -> Int -> Allocator -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Allocator -> Allocator -> IO ()
$cpoke :: Ptr Allocator -> Allocator -> IO ()
peek :: Ptr Allocator -> IO Allocator
$cpeek :: Ptr Allocator -> IO Allocator
pokeByteOff :: Ptr b -> Int -> Allocator -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Allocator -> IO ()
peekByteOff :: Ptr b -> Int -> IO Allocator
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Allocator
pokeElemOff :: Ptr Allocator -> Int -> Allocator -> IO ()
$cpokeElemOff :: Ptr Allocator -> Int -> Allocator -> IO ()
peekElemOff :: Ptr Allocator -> Int -> IO Allocator
$cpeekElemOff :: Ptr Allocator -> Int -> IO Allocator
alignment :: Allocator -> Int
$calignment :: Allocator -> Int
sizeOf :: Allocator -> Int
$csizeOf :: Allocator -> Int
Storable, Allocator
Allocator -> Zero Allocator
forall a. a -> Zero a
zero :: Allocator
$czero :: Allocator
Zero)
deriving anyclass (Eq Allocator
Zero Allocator
(Eq Allocator, Zero Allocator) => IsHandle Allocator
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Allocator
$cp1IsHandle :: Eq Allocator
IsHandle)
instance Show Allocator where
showsPrec :: Int -> Allocator -> ShowS
showsPrec p :: Int
p (Allocator x :: "lostAllocationCount" ::: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Allocator 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("lostAllocationCount" ::: Word64) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "lostAllocationCount" ::: Word64
x)
type FN_vmaAllocateDeviceMemoryFunction = Allocator -> ("memoryType" ::: Word32) -> DeviceMemory -> DeviceSize -> ("pUserData" ::: Ptr ()) -> IO ()
type PFN_vmaAllocateDeviceMemoryFunction = FunPtr FN_vmaAllocateDeviceMemoryFunction
type FN_vmaFreeDeviceMemoryFunction = Allocator -> ("memoryType" ::: Word32) -> DeviceMemory -> DeviceSize -> ("pUserData" ::: Ptr ()) -> IO ()
type PFN_vmaFreeDeviceMemoryFunction = FunPtr FN_vmaFreeDeviceMemoryFunction
data DeviceMemoryCallbacks = DeviceMemoryCallbacks
{
DeviceMemoryCallbacks -> PFN_vmaAllocateDeviceMemoryFunction
pfnAllocate :: PFN_vmaAllocateDeviceMemoryFunction
,
DeviceMemoryCallbacks -> PFN_vmaAllocateDeviceMemoryFunction
pfnFree :: PFN_vmaFreeDeviceMemoryFunction
,
DeviceMemoryCallbacks -> "userData" ::: Ptr ()
userData :: Ptr ()
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DeviceMemoryCallbacks)
#endif
deriving instance Show DeviceMemoryCallbacks
instance ToCStruct DeviceMemoryCallbacks where
withCStruct :: DeviceMemoryCallbacks
-> (Ptr DeviceMemoryCallbacks -> IO b) -> IO b
withCStruct x :: DeviceMemoryCallbacks
x f :: Ptr DeviceMemoryCallbacks -> IO b
f = Int -> Int -> (Ptr DeviceMemoryCallbacks -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DeviceMemoryCallbacks -> IO b) -> IO b)
-> (Ptr DeviceMemoryCallbacks -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DeviceMemoryCallbacks
p -> Ptr DeviceMemoryCallbacks -> DeviceMemoryCallbacks -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceMemoryCallbacks
p DeviceMemoryCallbacks
x (Ptr DeviceMemoryCallbacks -> IO b
f Ptr DeviceMemoryCallbacks
p)
pokeCStruct :: Ptr DeviceMemoryCallbacks -> DeviceMemoryCallbacks -> IO b -> IO b
pokeCStruct p :: Ptr DeviceMemoryCallbacks
p DeviceMemoryCallbacks{..} f :: IO b
f = do
Ptr PFN_vmaAllocateDeviceMemoryFunction
-> PFN_vmaAllocateDeviceMemoryFunction -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryCallbacks
p Ptr DeviceMemoryCallbacks
-> Int -> Ptr PFN_vmaAllocateDeviceMemoryFunction
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr PFN_vmaAllocateDeviceMemoryFunction)) (PFN_vmaAllocateDeviceMemoryFunction
pfnAllocate)
Ptr PFN_vmaAllocateDeviceMemoryFunction
-> PFN_vmaAllocateDeviceMemoryFunction -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryCallbacks
p Ptr DeviceMemoryCallbacks
-> Int -> Ptr PFN_vmaAllocateDeviceMemoryFunction
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PFN_vmaFreeDeviceMemoryFunction)) (PFN_vmaAllocateDeviceMemoryFunction
pfnFree)
Ptr ("userData" ::: Ptr ()) -> ("userData" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DeviceMemoryCallbacks
p Ptr DeviceMemoryCallbacks -> Int -> Ptr ("userData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr ()))) ("userData" ::: Ptr ()
userData)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr DeviceMemoryCallbacks -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
instance FromCStruct DeviceMemoryCallbacks where
peekCStruct :: Ptr DeviceMemoryCallbacks -> IO DeviceMemoryCallbacks
peekCStruct p :: Ptr DeviceMemoryCallbacks
p = do
PFN_vmaAllocateDeviceMemoryFunction
pfnAllocate <- Ptr PFN_vmaAllocateDeviceMemoryFunction
-> IO PFN_vmaAllocateDeviceMemoryFunction
forall a. Storable a => Ptr a -> IO a
peek @PFN_vmaAllocateDeviceMemoryFunction ((Ptr DeviceMemoryCallbacks
p Ptr DeviceMemoryCallbacks
-> Int -> Ptr PFN_vmaAllocateDeviceMemoryFunction
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr PFN_vmaAllocateDeviceMemoryFunction))
PFN_vmaAllocateDeviceMemoryFunction
pfnFree <- Ptr PFN_vmaAllocateDeviceMemoryFunction
-> IO PFN_vmaAllocateDeviceMemoryFunction
forall a. Storable a => Ptr a -> IO a
peek @PFN_vmaFreeDeviceMemoryFunction ((Ptr DeviceMemoryCallbacks
p Ptr DeviceMemoryCallbacks
-> Int -> Ptr PFN_vmaAllocateDeviceMemoryFunction
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PFN_vmaFreeDeviceMemoryFunction))
"userData" ::: Ptr ()
pUserData <- Ptr ("userData" ::: Ptr ()) -> IO ("userData" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr DeviceMemoryCallbacks
p Ptr DeviceMemoryCallbacks -> Int -> Ptr ("userData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr ())))
DeviceMemoryCallbacks -> IO DeviceMemoryCallbacks
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DeviceMemoryCallbacks -> IO DeviceMemoryCallbacks)
-> DeviceMemoryCallbacks -> IO DeviceMemoryCallbacks
forall a b. (a -> b) -> a -> b
$ PFN_vmaAllocateDeviceMemoryFunction
-> PFN_vmaAllocateDeviceMemoryFunction
-> ("userData" ::: Ptr ())
-> DeviceMemoryCallbacks
DeviceMemoryCallbacks
PFN_vmaAllocateDeviceMemoryFunction
pfnAllocate PFN_vmaAllocateDeviceMemoryFunction
pfnFree "userData" ::: Ptr ()
pUserData
instance Storable DeviceMemoryCallbacks where
sizeOf :: DeviceMemoryCallbacks -> Int
sizeOf ~DeviceMemoryCallbacks
_ = 24
alignment :: DeviceMemoryCallbacks -> Int
alignment ~DeviceMemoryCallbacks
_ = 8
peek :: Ptr DeviceMemoryCallbacks -> IO DeviceMemoryCallbacks
peek = Ptr DeviceMemoryCallbacks -> IO DeviceMemoryCallbacks
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DeviceMemoryCallbacks -> DeviceMemoryCallbacks -> IO ()
poke ptr :: Ptr DeviceMemoryCallbacks
ptr poked :: DeviceMemoryCallbacks
poked = Ptr DeviceMemoryCallbacks
-> DeviceMemoryCallbacks -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DeviceMemoryCallbacks
ptr DeviceMemoryCallbacks
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DeviceMemoryCallbacks where
zero :: DeviceMemoryCallbacks
zero = PFN_vmaAllocateDeviceMemoryFunction
-> PFN_vmaAllocateDeviceMemoryFunction
-> ("userData" ::: Ptr ())
-> DeviceMemoryCallbacks
DeviceMemoryCallbacks
PFN_vmaAllocateDeviceMemoryFunction
forall a. Zero a => a
zero
PFN_vmaAllocateDeviceMemoryFunction
forall a. Zero a => a
zero
"userData" ::: Ptr ()
forall a. Zero a => a
zero
newtype AllocatorCreateFlagBits = AllocatorCreateFlagBits Flags
deriving newtype (AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
(AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool)
-> (AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool)
-> Eq AllocatorCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
$c/= :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
== :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
$c== :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
Eq, Eq AllocatorCreateFlagBits
Eq AllocatorCreateFlagBits =>
(AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Ordering)
-> (AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool)
-> (AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool)
-> (AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool)
-> (AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool)
-> (AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits)
-> Ord AllocatorCreateFlagBits
AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Ordering
AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
$cmin :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
max :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
$cmax :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
>= :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
$c>= :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
> :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
$c> :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
<= :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
$c<= :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
< :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
$c< :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Bool
compare :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Ordering
$ccompare :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> Ordering
$cp1Ord :: Eq AllocatorCreateFlagBits
Ord, Ptr b -> Int -> IO AllocatorCreateFlagBits
Ptr b -> Int -> AllocatorCreateFlagBits -> IO ()
Ptr AllocatorCreateFlagBits -> IO AllocatorCreateFlagBits
Ptr AllocatorCreateFlagBits -> Int -> IO AllocatorCreateFlagBits
Ptr AllocatorCreateFlagBits
-> Int -> AllocatorCreateFlagBits -> IO ()
Ptr AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> IO ()
AllocatorCreateFlagBits -> Int
(AllocatorCreateFlagBits -> Int)
-> (AllocatorCreateFlagBits -> Int)
-> (Ptr AllocatorCreateFlagBits
-> Int -> IO AllocatorCreateFlagBits)
-> (Ptr AllocatorCreateFlagBits
-> Int -> AllocatorCreateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO AllocatorCreateFlagBits)
-> (forall b. Ptr b -> Int -> AllocatorCreateFlagBits -> IO ())
-> (Ptr AllocatorCreateFlagBits -> IO AllocatorCreateFlagBits)
-> (Ptr AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> IO ())
-> Storable AllocatorCreateFlagBits
forall b. Ptr b -> Int -> IO AllocatorCreateFlagBits
forall b. Ptr b -> Int -> AllocatorCreateFlagBits -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> IO ()
$cpoke :: Ptr AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> IO ()
peek :: Ptr AllocatorCreateFlagBits -> IO AllocatorCreateFlagBits
$cpeek :: Ptr AllocatorCreateFlagBits -> IO AllocatorCreateFlagBits
pokeByteOff :: Ptr b -> Int -> AllocatorCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AllocatorCreateFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO AllocatorCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AllocatorCreateFlagBits
pokeElemOff :: Ptr AllocatorCreateFlagBits
-> Int -> AllocatorCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr AllocatorCreateFlagBits
-> Int -> AllocatorCreateFlagBits -> IO ()
peekElemOff :: Ptr AllocatorCreateFlagBits -> Int -> IO AllocatorCreateFlagBits
$cpeekElemOff :: Ptr AllocatorCreateFlagBits -> Int -> IO AllocatorCreateFlagBits
alignment :: AllocatorCreateFlagBits -> Int
$calignment :: AllocatorCreateFlagBits -> Int
sizeOf :: AllocatorCreateFlagBits -> Int
$csizeOf :: AllocatorCreateFlagBits -> Int
Storable, AllocatorCreateFlagBits
AllocatorCreateFlagBits -> Zero AllocatorCreateFlagBits
forall a. a -> Zero a
zero :: AllocatorCreateFlagBits
$czero :: AllocatorCreateFlagBits
Zero, Eq AllocatorCreateFlagBits
AllocatorCreateFlagBits
Eq AllocatorCreateFlagBits =>
(AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> AllocatorCreateFlagBits
-> (Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> Bool)
-> (AllocatorCreateFlagBits -> Maybe Int)
-> (AllocatorCreateFlagBits -> Int)
-> (AllocatorCreateFlagBits -> Bool)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits)
-> (AllocatorCreateFlagBits -> Int)
-> Bits AllocatorCreateFlagBits
Int -> AllocatorCreateFlagBits
AllocatorCreateFlagBits -> Bool
AllocatorCreateFlagBits -> Int
AllocatorCreateFlagBits -> Maybe Int
AllocatorCreateFlagBits -> AllocatorCreateFlagBits
AllocatorCreateFlagBits -> Int -> Bool
AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: AllocatorCreateFlagBits -> Int
$cpopCount :: AllocatorCreateFlagBits -> Int
rotateR :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$crotateR :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
rotateL :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$crotateL :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
unsafeShiftR :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$cunsafeShiftR :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
shiftR :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$cshiftR :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
unsafeShiftL :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$cunsafeShiftL :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
shiftL :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$cshiftL :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
isSigned :: AllocatorCreateFlagBits -> Bool
$cisSigned :: AllocatorCreateFlagBits -> Bool
bitSize :: AllocatorCreateFlagBits -> Int
$cbitSize :: AllocatorCreateFlagBits -> Int
bitSizeMaybe :: AllocatorCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: AllocatorCreateFlagBits -> Maybe Int
testBit :: AllocatorCreateFlagBits -> Int -> Bool
$ctestBit :: AllocatorCreateFlagBits -> Int -> Bool
complementBit :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$ccomplementBit :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
clearBit :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$cclearBit :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
setBit :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$csetBit :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
bit :: Int -> AllocatorCreateFlagBits
$cbit :: Int -> AllocatorCreateFlagBits
zeroBits :: AllocatorCreateFlagBits
$czeroBits :: AllocatorCreateFlagBits
rotate :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$crotate :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
shift :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
$cshift :: AllocatorCreateFlagBits -> Int -> AllocatorCreateFlagBits
complement :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits
$ccomplement :: AllocatorCreateFlagBits -> AllocatorCreateFlagBits
xor :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
$cxor :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
.|. :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
$c.|. :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
.&. :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
$c.&. :: AllocatorCreateFlagBits
-> AllocatorCreateFlagBits -> AllocatorCreateFlagBits
$cp1Bits :: Eq AllocatorCreateFlagBits
Bits)
pattern $bALLOCATOR_CREATE_EXTERNALLY_SYNCHRONIZED_BIT :: AllocatorCreateFlagBits
$mALLOCATOR_CREATE_EXTERNALLY_SYNCHRONIZED_BIT :: forall r.
AllocatorCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATOR_CREATE_EXTERNALLY_SYNCHRONIZED_BIT = AllocatorCreateFlagBits 0x00000001
pattern $bALLOCATOR_CREATE_KHR_DEDICATED_ALLOCATION_BIT :: AllocatorCreateFlagBits
$mALLOCATOR_CREATE_KHR_DEDICATED_ALLOCATION_BIT :: forall r.
AllocatorCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATOR_CREATE_KHR_DEDICATED_ALLOCATION_BIT = AllocatorCreateFlagBits 0x00000002
pattern $bALLOCATOR_CREATE_KHR_BIND_MEMORY2_BIT :: AllocatorCreateFlagBits
$mALLOCATOR_CREATE_KHR_BIND_MEMORY2_BIT :: forall r.
AllocatorCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATOR_CREATE_KHR_BIND_MEMORY2_BIT = AllocatorCreateFlagBits 0x00000004
pattern $bALLOCATOR_CREATE_EXT_MEMORY_BUDGET_BIT :: AllocatorCreateFlagBits
$mALLOCATOR_CREATE_EXT_MEMORY_BUDGET_BIT :: forall r.
AllocatorCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATOR_CREATE_EXT_MEMORY_BUDGET_BIT = AllocatorCreateFlagBits 0x00000008
pattern $bALLOCATOR_CREATE_AMD_DEVICE_COHERENT_MEMORY_BIT :: AllocatorCreateFlagBits
$mALLOCATOR_CREATE_AMD_DEVICE_COHERENT_MEMORY_BIT :: forall r.
AllocatorCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATOR_CREATE_AMD_DEVICE_COHERENT_MEMORY_BIT = AllocatorCreateFlagBits 0x00000010
pattern $bALLOCATOR_CREATE_BUFFER_DEVICE_ADDRESS_BIT :: AllocatorCreateFlagBits
$mALLOCATOR_CREATE_BUFFER_DEVICE_ADDRESS_BIT :: forall r.
AllocatorCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATOR_CREATE_BUFFER_DEVICE_ADDRESS_BIT = AllocatorCreateFlagBits 0x00000020
type AllocatorCreateFlags = AllocatorCreateFlagBits
instance Show AllocatorCreateFlagBits where
showsPrec :: Int -> AllocatorCreateFlagBits -> ShowS
showsPrec p :: Int
p = \case
ALLOCATOR_CREATE_EXTERNALLY_SYNCHRONIZED_BIT -> String -> ShowS
showString "ALLOCATOR_CREATE_EXTERNALLY_SYNCHRONIZED_BIT"
ALLOCATOR_CREATE_KHR_DEDICATED_ALLOCATION_BIT -> String -> ShowS
showString "ALLOCATOR_CREATE_KHR_DEDICATED_ALLOCATION_BIT"
ALLOCATOR_CREATE_KHR_BIND_MEMORY2_BIT -> String -> ShowS
showString "ALLOCATOR_CREATE_KHR_BIND_MEMORY2_BIT"
ALLOCATOR_CREATE_EXT_MEMORY_BUDGET_BIT -> String -> ShowS
showString "ALLOCATOR_CREATE_EXT_MEMORY_BUDGET_BIT"
ALLOCATOR_CREATE_AMD_DEVICE_COHERENT_MEMORY_BIT -> String -> ShowS
showString "ALLOCATOR_CREATE_AMD_DEVICE_COHERENT_MEMORY_BIT"
ALLOCATOR_CREATE_BUFFER_DEVICE_ADDRESS_BIT -> String -> ShowS
showString "ALLOCATOR_CREATE_BUFFER_DEVICE_ADDRESS_BIT"
AllocatorCreateFlagBits x :: "memoryTypeIndex" ::: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "AllocatorCreateFlagBits 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("memoryTypeIndex" ::: Word32) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "memoryTypeIndex" ::: Word32
x)
instance Read AllocatorCreateFlagBits where
readPrec :: ReadPrec AllocatorCreateFlagBits
readPrec = ReadPrec AllocatorCreateFlagBits
-> ReadPrec AllocatorCreateFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec AllocatorCreateFlagBits)]
-> ReadPrec AllocatorCreateFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("ALLOCATOR_CREATE_EXTERNALLY_SYNCHRONIZED_BIT", AllocatorCreateFlagBits -> ReadPrec AllocatorCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocatorCreateFlagBits
ALLOCATOR_CREATE_EXTERNALLY_SYNCHRONIZED_BIT)
, ("ALLOCATOR_CREATE_KHR_DEDICATED_ALLOCATION_BIT", AllocatorCreateFlagBits -> ReadPrec AllocatorCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocatorCreateFlagBits
ALLOCATOR_CREATE_KHR_DEDICATED_ALLOCATION_BIT)
, ("ALLOCATOR_CREATE_KHR_BIND_MEMORY2_BIT", AllocatorCreateFlagBits -> ReadPrec AllocatorCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocatorCreateFlagBits
ALLOCATOR_CREATE_KHR_BIND_MEMORY2_BIT)
, ("ALLOCATOR_CREATE_EXT_MEMORY_BUDGET_BIT", AllocatorCreateFlagBits -> ReadPrec AllocatorCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocatorCreateFlagBits
ALLOCATOR_CREATE_EXT_MEMORY_BUDGET_BIT)
, ("ALLOCATOR_CREATE_AMD_DEVICE_COHERENT_MEMORY_BIT", AllocatorCreateFlagBits -> ReadPrec AllocatorCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocatorCreateFlagBits
ALLOCATOR_CREATE_AMD_DEVICE_COHERENT_MEMORY_BIT)
, ("ALLOCATOR_CREATE_BUFFER_DEVICE_ADDRESS_BIT", AllocatorCreateFlagBits -> ReadPrec AllocatorCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocatorCreateFlagBits
ALLOCATOR_CREATE_BUFFER_DEVICE_ADDRESS_BIT)]
ReadPrec AllocatorCreateFlagBits
-> ReadPrec AllocatorCreateFlagBits
-> ReadPrec AllocatorCreateFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec AllocatorCreateFlagBits
-> ReadPrec AllocatorCreateFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "AllocatorCreateFlagBits")
"memoryTypeIndex" ::: Word32
v <- ReadPrec ("memoryTypeIndex" ::: Word32)
-> ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. Read a => ReadPrec a
readPrec
AllocatorCreateFlagBits -> ReadPrec AllocatorCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("memoryTypeIndex" ::: Word32) -> AllocatorCreateFlagBits
AllocatorCreateFlagBits "memoryTypeIndex" ::: Word32
v)))
data VulkanFunctions = VulkanFunctions
{
VulkanFunctions -> PFN_vkGetPhysicalDeviceProperties
vkGetPhysicalDeviceProperties :: PFN_vkGetPhysicalDeviceProperties
,
VulkanFunctions -> PFN_vkGetPhysicalDeviceMemoryProperties
vkGetPhysicalDeviceMemoryProperties :: PFN_vkGetPhysicalDeviceMemoryProperties
,
VulkanFunctions -> PFN_vkAllocateMemory
vkAllocateMemory :: PFN_vkAllocateMemory
,
VulkanFunctions -> PFN_vkFreeMemory
vkFreeMemory :: PFN_vkFreeMemory
,
VulkanFunctions -> PFN_vkMapMemory
vkMapMemory :: PFN_vkMapMemory
,
VulkanFunctions -> PFN_vkUnmapMemory
vkUnmapMemory :: PFN_vkUnmapMemory
,
VulkanFunctions -> PFN_vkFlushMappedMemoryRanges
vkFlushMappedMemoryRanges :: PFN_vkFlushMappedMemoryRanges
,
VulkanFunctions -> PFN_vkFlushMappedMemoryRanges
vkInvalidateMappedMemoryRanges :: PFN_vkInvalidateMappedMemoryRanges
,
VulkanFunctions -> PFN_vkBindBufferMemory
vkBindBufferMemory :: PFN_vkBindBufferMemory
,
VulkanFunctions -> PFN_vkBindImageMemory
vkBindImageMemory :: PFN_vkBindImageMemory
,
VulkanFunctions -> PFN_vkGetBufferMemoryRequirements
vkGetBufferMemoryRequirements :: PFN_vkGetBufferMemoryRequirements
,
VulkanFunctions -> PFN_vkGetImageMemoryRequirements
vkGetImageMemoryRequirements :: PFN_vkGetImageMemoryRequirements
,
VulkanFunctions -> PFN_vkCreateBuffer
vkCreateBuffer :: PFN_vkCreateBuffer
,
VulkanFunctions -> PFN_vkDestroyBuffer
vkDestroyBuffer :: PFN_vkDestroyBuffer
,
VulkanFunctions -> PFN_vkCreateImage
vkCreateImage :: PFN_vkCreateImage
,
VulkanFunctions -> PFN_vkDestroyImage
vkDestroyImage :: PFN_vkDestroyImage
,
VulkanFunctions -> PFN_vkCmdCopyBuffer
vkCmdCopyBuffer :: PFN_vkCmdCopyBuffer
,
VulkanFunctions -> PFN_vkGetBufferMemoryRequirements2KHR
vkGetBufferMemoryRequirements2KHR :: PFN_vkGetBufferMemoryRequirements2KHR
,
VulkanFunctions -> PFN_vkGetImageMemoryRequirements2KHR
vkGetImageMemoryRequirements2KHR :: PFN_vkGetImageMemoryRequirements2KHR
,
VulkanFunctions -> PFN_vkBindBufferMemory2KHR
vkBindBufferMemory2KHR :: PFN_vkBindBufferMemory2KHR
,
VulkanFunctions -> PFN_vkBindImageMemory2KHR
vkBindImageMemory2KHR :: PFN_vkBindImageMemory2KHR
,
VulkanFunctions -> PFN_vkGetPhysicalDeviceMemoryProperties2KHR
vkGetPhysicalDeviceMemoryProperties2KHR :: PFN_vkGetPhysicalDeviceMemoryProperties2KHR
}
deriving (Typeable, VulkanFunctions -> VulkanFunctions -> Bool
(VulkanFunctions -> VulkanFunctions -> Bool)
-> (VulkanFunctions -> VulkanFunctions -> Bool)
-> Eq VulkanFunctions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VulkanFunctions -> VulkanFunctions -> Bool
$c/= :: VulkanFunctions -> VulkanFunctions -> Bool
== :: VulkanFunctions -> VulkanFunctions -> Bool
$c== :: VulkanFunctions -> VulkanFunctions -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (VulkanFunctions)
#endif
deriving instance Show VulkanFunctions
instance ToCStruct VulkanFunctions where
withCStruct :: VulkanFunctions -> (Ptr VulkanFunctions -> IO b) -> IO b
withCStruct x :: VulkanFunctions
x f :: Ptr VulkanFunctions -> IO b
f = Int -> Int -> (Ptr VulkanFunctions -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 176 8 ((Ptr VulkanFunctions -> IO b) -> IO b)
-> (Ptr VulkanFunctions -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr VulkanFunctions
p -> Ptr VulkanFunctions -> VulkanFunctions -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr VulkanFunctions
p VulkanFunctions
x (Ptr VulkanFunctions -> IO b
f Ptr VulkanFunctions
p)
pokeCStruct :: Ptr VulkanFunctions -> VulkanFunctions -> IO b -> IO b
pokeCStruct p :: Ptr VulkanFunctions
p VulkanFunctions{..} f :: IO b
f = do
Ptr PFN_vkGetPhysicalDeviceProperties
-> PFN_vkGetPhysicalDeviceProperties -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkGetPhysicalDeviceProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr PFN_vkGetPhysicalDeviceProperties)) (PFN_vkGetPhysicalDeviceProperties
vkGetPhysicalDeviceProperties)
Ptr PFN_vkGetPhysicalDeviceMemoryProperties
-> PFN_vkGetPhysicalDeviceMemoryProperties -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions
-> Int -> Ptr PFN_vkGetPhysicalDeviceMemoryProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PFN_vkGetPhysicalDeviceMemoryProperties)) (PFN_vkGetPhysicalDeviceMemoryProperties
vkGetPhysicalDeviceMemoryProperties)
Ptr PFN_vkAllocateMemory -> PFN_vkAllocateMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkAllocateMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PFN_vkAllocateMemory)) (PFN_vkAllocateMemory
vkAllocateMemory)
Ptr PFN_vkFreeMemory -> PFN_vkFreeMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkFreeMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr PFN_vkFreeMemory)) (PFN_vkFreeMemory
vkFreeMemory)
Ptr PFN_vkMapMemory -> PFN_vkMapMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkMapMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr PFN_vkMapMemory)) (PFN_vkMapMemory
vkMapMemory)
Ptr PFN_vkUnmapMemory -> PFN_vkUnmapMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkUnmapMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr PFN_vkUnmapMemory)) (PFN_vkUnmapMemory
vkUnmapMemory)
Ptr PFN_vkFlushMappedMemoryRanges
-> PFN_vkFlushMappedMemoryRanges -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkFlushMappedMemoryRanges
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr PFN_vkFlushMappedMemoryRanges)) (PFN_vkFlushMappedMemoryRanges
vkFlushMappedMemoryRanges)
Ptr PFN_vkFlushMappedMemoryRanges
-> PFN_vkFlushMappedMemoryRanges -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkFlushMappedMemoryRanges
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr PFN_vkInvalidateMappedMemoryRanges)) (PFN_vkFlushMappedMemoryRanges
vkInvalidateMappedMemoryRanges)
Ptr PFN_vkBindBufferMemory -> PFN_vkBindBufferMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkBindBufferMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr PFN_vkBindBufferMemory)) (PFN_vkBindBufferMemory
vkBindBufferMemory)
Ptr PFN_vkBindImageMemory -> PFN_vkBindImageMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkBindImageMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr PFN_vkBindImageMemory)) (PFN_vkBindImageMemory
vkBindImageMemory)
Ptr PFN_vkGetBufferMemoryRequirements
-> PFN_vkGetBufferMemoryRequirements -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkGetBufferMemoryRequirements
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr PFN_vkGetBufferMemoryRequirements)) (PFN_vkGetBufferMemoryRequirements
vkGetBufferMemoryRequirements)
Ptr PFN_vkGetImageMemoryRequirements
-> PFN_vkGetImageMemoryRequirements -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkGetImageMemoryRequirements
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr PFN_vkGetImageMemoryRequirements)) (PFN_vkGetImageMemoryRequirements
vkGetImageMemoryRequirements)
Ptr PFN_vkCreateBuffer -> PFN_vkCreateBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkCreateBuffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr PFN_vkCreateBuffer)) (PFN_vkCreateBuffer
vkCreateBuffer)
Ptr PFN_vkDestroyBuffer -> PFN_vkDestroyBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkDestroyBuffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr PFN_vkDestroyBuffer)) (PFN_vkDestroyBuffer
vkDestroyBuffer)
Ptr PFN_vkCreateImage -> PFN_vkCreateImage -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkCreateImage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr PFN_vkCreateImage)) (PFN_vkCreateImage
vkCreateImage)
Ptr PFN_vkDestroyImage -> PFN_vkDestroyImage -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkDestroyImage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr PFN_vkDestroyImage)) (PFN_vkDestroyImage
vkDestroyImage)
Ptr PFN_vkCmdCopyBuffer -> PFN_vkCmdCopyBuffer -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkCmdCopyBuffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr PFN_vkCmdCopyBuffer)) (PFN_vkCmdCopyBuffer
vkCmdCopyBuffer)
Ptr PFN_vkGetBufferMemoryRequirements2KHR
-> PFN_vkGetBufferMemoryRequirements2KHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions
-> Int -> Ptr PFN_vkGetBufferMemoryRequirements2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr PFN_vkGetBufferMemoryRequirements2KHR)) (PFN_vkGetBufferMemoryRequirements2KHR
vkGetBufferMemoryRequirements2KHR)
Ptr PFN_vkGetImageMemoryRequirements2KHR
-> PFN_vkGetImageMemoryRequirements2KHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions
-> Int -> Ptr PFN_vkGetImageMemoryRequirements2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr PFN_vkGetImageMemoryRequirements2KHR)) (PFN_vkGetImageMemoryRequirements2KHR
vkGetImageMemoryRequirements2KHR)
Ptr PFN_vkBindBufferMemory2KHR
-> PFN_vkBindBufferMemory2KHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkBindBufferMemory2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr PFN_vkBindBufferMemory2KHR)) (PFN_vkBindBufferMemory2KHR
vkBindBufferMemory2KHR)
Ptr PFN_vkBindImageMemory2KHR -> PFN_vkBindImageMemory2KHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkBindImageMemory2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr PFN_vkBindImageMemory2KHR)) (PFN_vkBindImageMemory2KHR
vkBindImageMemory2KHR)
Ptr PFN_vkGetPhysicalDeviceMemoryProperties2KHR
-> PFN_vkGetPhysicalDeviceMemoryProperties2KHR -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr VulkanFunctions
p Ptr VulkanFunctions
-> Int -> Ptr PFN_vkGetPhysicalDeviceMemoryProperties2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr PFN_vkGetPhysicalDeviceMemoryProperties2KHR)) (PFN_vkGetPhysicalDeviceMemoryProperties2KHR
vkGetPhysicalDeviceMemoryProperties2KHR)
IO b
f
cStructSize :: Int
cStructSize = 176
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr VulkanFunctions -> IO b -> IO b
pokeZeroCStruct _ f :: IO b
f = IO b
f
instance FromCStruct VulkanFunctions where
peekCStruct :: Ptr VulkanFunctions -> IO VulkanFunctions
peekCStruct p :: Ptr VulkanFunctions
p = do
PFN_vkGetPhysicalDeviceProperties
vkGetPhysicalDeviceProperties <- Ptr PFN_vkGetPhysicalDeviceProperties
-> IO PFN_vkGetPhysicalDeviceProperties
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkGetPhysicalDeviceProperties ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkGetPhysicalDeviceProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr PFN_vkGetPhysicalDeviceProperties))
PFN_vkGetPhysicalDeviceMemoryProperties
vkGetPhysicalDeviceMemoryProperties <- Ptr PFN_vkGetPhysicalDeviceMemoryProperties
-> IO PFN_vkGetPhysicalDeviceMemoryProperties
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkGetPhysicalDeviceMemoryProperties ((Ptr VulkanFunctions
p Ptr VulkanFunctions
-> Int -> Ptr PFN_vkGetPhysicalDeviceMemoryProperties
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr PFN_vkGetPhysicalDeviceMemoryProperties))
PFN_vkAllocateMemory
vkAllocateMemory <- Ptr PFN_vkAllocateMemory -> IO PFN_vkAllocateMemory
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkAllocateMemory ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkAllocateMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr PFN_vkAllocateMemory))
PFN_vkFreeMemory
vkFreeMemory <- Ptr PFN_vkFreeMemory -> IO PFN_vkFreeMemory
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkFreeMemory ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkFreeMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr PFN_vkFreeMemory))
PFN_vkMapMemory
vkMapMemory <- Ptr PFN_vkMapMemory -> IO PFN_vkMapMemory
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkMapMemory ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkMapMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr PFN_vkMapMemory))
PFN_vkUnmapMemory
vkUnmapMemory <- Ptr PFN_vkUnmapMemory -> IO PFN_vkUnmapMemory
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkUnmapMemory ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkUnmapMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr PFN_vkUnmapMemory))
PFN_vkFlushMappedMemoryRanges
vkFlushMappedMemoryRanges <- Ptr PFN_vkFlushMappedMemoryRanges
-> IO PFN_vkFlushMappedMemoryRanges
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkFlushMappedMemoryRanges ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkFlushMappedMemoryRanges
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr PFN_vkFlushMappedMemoryRanges))
PFN_vkFlushMappedMemoryRanges
vkInvalidateMappedMemoryRanges <- Ptr PFN_vkFlushMappedMemoryRanges
-> IO PFN_vkFlushMappedMemoryRanges
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkInvalidateMappedMemoryRanges ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkFlushMappedMemoryRanges
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr PFN_vkInvalidateMappedMemoryRanges))
PFN_vkBindBufferMemory
vkBindBufferMemory <- Ptr PFN_vkBindBufferMemory -> IO PFN_vkBindBufferMemory
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkBindBufferMemory ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkBindBufferMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr PFN_vkBindBufferMemory))
PFN_vkBindImageMemory
vkBindImageMemory <- Ptr PFN_vkBindImageMemory -> IO PFN_vkBindImageMemory
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkBindImageMemory ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkBindImageMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr PFN_vkBindImageMemory))
PFN_vkGetBufferMemoryRequirements
vkGetBufferMemoryRequirements <- Ptr PFN_vkGetBufferMemoryRequirements
-> IO PFN_vkGetBufferMemoryRequirements
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkGetBufferMemoryRequirements ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkGetBufferMemoryRequirements
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr PFN_vkGetBufferMemoryRequirements))
PFN_vkGetImageMemoryRequirements
vkGetImageMemoryRequirements <- Ptr PFN_vkGetImageMemoryRequirements
-> IO PFN_vkGetImageMemoryRequirements
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkGetImageMemoryRequirements ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkGetImageMemoryRequirements
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr PFN_vkGetImageMemoryRequirements))
PFN_vkCreateBuffer
vkCreateBuffer <- Ptr PFN_vkCreateBuffer -> IO PFN_vkCreateBuffer
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkCreateBuffer ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkCreateBuffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 96 :: Ptr PFN_vkCreateBuffer))
PFN_vkDestroyBuffer
vkDestroyBuffer <- Ptr PFN_vkDestroyBuffer -> IO PFN_vkDestroyBuffer
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkDestroyBuffer ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkDestroyBuffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 104 :: Ptr PFN_vkDestroyBuffer))
PFN_vkCreateImage
vkCreateImage <- Ptr PFN_vkCreateImage -> IO PFN_vkCreateImage
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkCreateImage ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkCreateImage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 112 :: Ptr PFN_vkCreateImage))
PFN_vkDestroyImage
vkDestroyImage <- Ptr PFN_vkDestroyImage -> IO PFN_vkDestroyImage
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkDestroyImage ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkDestroyImage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 120 :: Ptr PFN_vkDestroyImage))
PFN_vkCmdCopyBuffer
vkCmdCopyBuffer <- Ptr PFN_vkCmdCopyBuffer -> IO PFN_vkCmdCopyBuffer
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkCmdCopyBuffer ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkCmdCopyBuffer
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 128 :: Ptr PFN_vkCmdCopyBuffer))
PFN_vkGetBufferMemoryRequirements2KHR
vkGetBufferMemoryRequirements2KHR <- Ptr PFN_vkGetBufferMemoryRequirements2KHR
-> IO PFN_vkGetBufferMemoryRequirements2KHR
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkGetBufferMemoryRequirements2KHR ((Ptr VulkanFunctions
p Ptr VulkanFunctions
-> Int -> Ptr PFN_vkGetBufferMemoryRequirements2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 136 :: Ptr PFN_vkGetBufferMemoryRequirements2KHR))
PFN_vkGetImageMemoryRequirements2KHR
vkGetImageMemoryRequirements2KHR <- Ptr PFN_vkGetImageMemoryRequirements2KHR
-> IO PFN_vkGetImageMemoryRequirements2KHR
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkGetImageMemoryRequirements2KHR ((Ptr VulkanFunctions
p Ptr VulkanFunctions
-> Int -> Ptr PFN_vkGetImageMemoryRequirements2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 144 :: Ptr PFN_vkGetImageMemoryRequirements2KHR))
PFN_vkBindBufferMemory2KHR
vkBindBufferMemory2KHR <- Ptr PFN_vkBindBufferMemory2KHR -> IO PFN_vkBindBufferMemory2KHR
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkBindBufferMemory2KHR ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkBindBufferMemory2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 152 :: Ptr PFN_vkBindBufferMemory2KHR))
PFN_vkBindImageMemory2KHR
vkBindImageMemory2KHR <- Ptr PFN_vkBindImageMemory2KHR -> IO PFN_vkBindImageMemory2KHR
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkBindImageMemory2KHR ((Ptr VulkanFunctions
p Ptr VulkanFunctions -> Int -> Ptr PFN_vkBindImageMemory2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 160 :: Ptr PFN_vkBindImageMemory2KHR))
PFN_vkGetPhysicalDeviceMemoryProperties2KHR
vkGetPhysicalDeviceMemoryProperties2KHR <- Ptr PFN_vkGetPhysicalDeviceMemoryProperties2KHR
-> IO PFN_vkGetPhysicalDeviceMemoryProperties2KHR
forall a. Storable a => Ptr a -> IO a
peek @PFN_vkGetPhysicalDeviceMemoryProperties2KHR ((Ptr VulkanFunctions
p Ptr VulkanFunctions
-> Int -> Ptr PFN_vkGetPhysicalDeviceMemoryProperties2KHR
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 168 :: Ptr PFN_vkGetPhysicalDeviceMemoryProperties2KHR))
VulkanFunctions -> IO VulkanFunctions
forall (f :: * -> *) a. Applicative f => a -> f a
pure (VulkanFunctions -> IO VulkanFunctions)
-> VulkanFunctions -> IO VulkanFunctions
forall a b. (a -> b) -> a -> b
$ PFN_vkGetPhysicalDeviceProperties
-> PFN_vkGetPhysicalDeviceMemoryProperties
-> PFN_vkAllocateMemory
-> PFN_vkFreeMemory
-> PFN_vkMapMemory
-> PFN_vkUnmapMemory
-> PFN_vkFlushMappedMemoryRanges
-> PFN_vkFlushMappedMemoryRanges
-> PFN_vkBindBufferMemory
-> PFN_vkBindImageMemory
-> PFN_vkGetBufferMemoryRequirements
-> PFN_vkGetImageMemoryRequirements
-> PFN_vkCreateBuffer
-> PFN_vkDestroyBuffer
-> PFN_vkCreateImage
-> PFN_vkDestroyImage
-> PFN_vkCmdCopyBuffer
-> PFN_vkGetBufferMemoryRequirements2KHR
-> PFN_vkGetImageMemoryRequirements2KHR
-> PFN_vkBindBufferMemory2KHR
-> PFN_vkBindImageMemory2KHR
-> PFN_vkGetPhysicalDeviceMemoryProperties2KHR
-> VulkanFunctions
VulkanFunctions
PFN_vkGetPhysicalDeviceProperties
vkGetPhysicalDeviceProperties PFN_vkGetPhysicalDeviceMemoryProperties
vkGetPhysicalDeviceMemoryProperties PFN_vkAllocateMemory
vkAllocateMemory PFN_vkFreeMemory
vkFreeMemory PFN_vkMapMemory
vkMapMemory PFN_vkUnmapMemory
vkUnmapMemory PFN_vkFlushMappedMemoryRanges
vkFlushMappedMemoryRanges PFN_vkFlushMappedMemoryRanges
vkInvalidateMappedMemoryRanges PFN_vkBindBufferMemory
vkBindBufferMemory PFN_vkBindImageMemory
vkBindImageMemory PFN_vkGetBufferMemoryRequirements
vkGetBufferMemoryRequirements PFN_vkGetImageMemoryRequirements
vkGetImageMemoryRequirements PFN_vkCreateBuffer
vkCreateBuffer PFN_vkDestroyBuffer
vkDestroyBuffer PFN_vkCreateImage
vkCreateImage PFN_vkDestroyImage
vkDestroyImage PFN_vkCmdCopyBuffer
vkCmdCopyBuffer PFN_vkGetBufferMemoryRequirements2KHR
vkGetBufferMemoryRequirements2KHR PFN_vkGetImageMemoryRequirements2KHR
vkGetImageMemoryRequirements2KHR PFN_vkBindBufferMemory2KHR
vkBindBufferMemory2KHR PFN_vkBindImageMemory2KHR
vkBindImageMemory2KHR PFN_vkGetPhysicalDeviceMemoryProperties2KHR
vkGetPhysicalDeviceMemoryProperties2KHR
instance Storable VulkanFunctions where
sizeOf :: VulkanFunctions -> Int
sizeOf ~VulkanFunctions
_ = 176
alignment :: VulkanFunctions -> Int
alignment ~VulkanFunctions
_ = 8
peek :: Ptr VulkanFunctions -> IO VulkanFunctions
peek = Ptr VulkanFunctions -> IO VulkanFunctions
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr VulkanFunctions -> VulkanFunctions -> IO ()
poke ptr :: Ptr VulkanFunctions
ptr poked :: VulkanFunctions
poked = Ptr VulkanFunctions -> VulkanFunctions -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr VulkanFunctions
ptr VulkanFunctions
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero VulkanFunctions where
zero :: VulkanFunctions
zero = PFN_vkGetPhysicalDeviceProperties
-> PFN_vkGetPhysicalDeviceMemoryProperties
-> PFN_vkAllocateMemory
-> PFN_vkFreeMemory
-> PFN_vkMapMemory
-> PFN_vkUnmapMemory
-> PFN_vkFlushMappedMemoryRanges
-> PFN_vkFlushMappedMemoryRanges
-> PFN_vkBindBufferMemory
-> PFN_vkBindImageMemory
-> PFN_vkGetBufferMemoryRequirements
-> PFN_vkGetImageMemoryRequirements
-> PFN_vkCreateBuffer
-> PFN_vkDestroyBuffer
-> PFN_vkCreateImage
-> PFN_vkDestroyImage
-> PFN_vkCmdCopyBuffer
-> PFN_vkGetBufferMemoryRequirements2KHR
-> PFN_vkGetImageMemoryRequirements2KHR
-> PFN_vkBindBufferMemory2KHR
-> PFN_vkBindImageMemory2KHR
-> PFN_vkGetPhysicalDeviceMemoryProperties2KHR
-> VulkanFunctions
VulkanFunctions
PFN_vkGetPhysicalDeviceProperties
forall a. Zero a => a
zero
PFN_vkGetPhysicalDeviceMemoryProperties
forall a. Zero a => a
zero
PFN_vkAllocateMemory
forall a. Zero a => a
zero
PFN_vkFreeMemory
forall a. Zero a => a
zero
PFN_vkMapMemory
forall a. Zero a => a
zero
PFN_vkUnmapMemory
forall a. Zero a => a
zero
PFN_vkFlushMappedMemoryRanges
forall a. Zero a => a
zero
PFN_vkFlushMappedMemoryRanges
forall a. Zero a => a
zero
PFN_vkBindBufferMemory
forall a. Zero a => a
zero
PFN_vkBindImageMemory
forall a. Zero a => a
zero
PFN_vkGetBufferMemoryRequirements
forall a. Zero a => a
zero
PFN_vkGetImageMemoryRequirements
forall a. Zero a => a
zero
PFN_vkCreateBuffer
forall a. Zero a => a
zero
PFN_vkDestroyBuffer
forall a. Zero a => a
zero
PFN_vkCreateImage
forall a. Zero a => a
zero
PFN_vkDestroyImage
forall a. Zero a => a
zero
PFN_vkCmdCopyBuffer
forall a. Zero a => a
zero
PFN_vkGetBufferMemoryRequirements2KHR
forall a. Zero a => a
zero
PFN_vkGetImageMemoryRequirements2KHR
forall a. Zero a => a
zero
PFN_vkBindBufferMemory2KHR
forall a. Zero a => a
zero
PFN_vkBindImageMemory2KHR
forall a. Zero a => a
zero
PFN_vkGetPhysicalDeviceMemoryProperties2KHR
forall a. Zero a => a
zero
newtype RecordFlagBits = RecordFlagBits Flags
deriving newtype (RecordFlagBits -> RecordFlagBits -> Bool
(RecordFlagBits -> RecordFlagBits -> Bool)
-> (RecordFlagBits -> RecordFlagBits -> Bool) -> Eq RecordFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecordFlagBits -> RecordFlagBits -> Bool
$c/= :: RecordFlagBits -> RecordFlagBits -> Bool
== :: RecordFlagBits -> RecordFlagBits -> Bool
$c== :: RecordFlagBits -> RecordFlagBits -> Bool
Eq, Eq RecordFlagBits
Eq RecordFlagBits =>
(RecordFlagBits -> RecordFlagBits -> Ordering)
-> (RecordFlagBits -> RecordFlagBits -> Bool)
-> (RecordFlagBits -> RecordFlagBits -> Bool)
-> (RecordFlagBits -> RecordFlagBits -> Bool)
-> (RecordFlagBits -> RecordFlagBits -> Bool)
-> (RecordFlagBits -> RecordFlagBits -> RecordFlagBits)
-> (RecordFlagBits -> RecordFlagBits -> RecordFlagBits)
-> Ord RecordFlagBits
RecordFlagBits -> RecordFlagBits -> Bool
RecordFlagBits -> RecordFlagBits -> Ordering
RecordFlagBits -> RecordFlagBits -> RecordFlagBits
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
$cmin :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
max :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
$cmax :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
>= :: RecordFlagBits -> RecordFlagBits -> Bool
$c>= :: RecordFlagBits -> RecordFlagBits -> Bool
> :: RecordFlagBits -> RecordFlagBits -> Bool
$c> :: RecordFlagBits -> RecordFlagBits -> Bool
<= :: RecordFlagBits -> RecordFlagBits -> Bool
$c<= :: RecordFlagBits -> RecordFlagBits -> Bool
< :: RecordFlagBits -> RecordFlagBits -> Bool
$c< :: RecordFlagBits -> RecordFlagBits -> Bool
compare :: RecordFlagBits -> RecordFlagBits -> Ordering
$ccompare :: RecordFlagBits -> RecordFlagBits -> Ordering
$cp1Ord :: Eq RecordFlagBits
Ord, Ptr b -> Int -> IO RecordFlagBits
Ptr b -> Int -> RecordFlagBits -> IO ()
Ptr RecordFlagBits -> IO RecordFlagBits
Ptr RecordFlagBits -> Int -> IO RecordFlagBits
Ptr RecordFlagBits -> Int -> RecordFlagBits -> IO ()
Ptr RecordFlagBits -> RecordFlagBits -> IO ()
RecordFlagBits -> Int
(RecordFlagBits -> Int)
-> (RecordFlagBits -> Int)
-> (Ptr RecordFlagBits -> Int -> IO RecordFlagBits)
-> (Ptr RecordFlagBits -> Int -> RecordFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO RecordFlagBits)
-> (forall b. Ptr b -> Int -> RecordFlagBits -> IO ())
-> (Ptr RecordFlagBits -> IO RecordFlagBits)
-> (Ptr RecordFlagBits -> RecordFlagBits -> IO ())
-> Storable RecordFlagBits
forall b. Ptr b -> Int -> IO RecordFlagBits
forall b. Ptr b -> Int -> RecordFlagBits -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr RecordFlagBits -> RecordFlagBits -> IO ()
$cpoke :: Ptr RecordFlagBits -> RecordFlagBits -> IO ()
peek :: Ptr RecordFlagBits -> IO RecordFlagBits
$cpeek :: Ptr RecordFlagBits -> IO RecordFlagBits
pokeByteOff :: Ptr b -> Int -> RecordFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> RecordFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO RecordFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO RecordFlagBits
pokeElemOff :: Ptr RecordFlagBits -> Int -> RecordFlagBits -> IO ()
$cpokeElemOff :: Ptr RecordFlagBits -> Int -> RecordFlagBits -> IO ()
peekElemOff :: Ptr RecordFlagBits -> Int -> IO RecordFlagBits
$cpeekElemOff :: Ptr RecordFlagBits -> Int -> IO RecordFlagBits
alignment :: RecordFlagBits -> Int
$calignment :: RecordFlagBits -> Int
sizeOf :: RecordFlagBits -> Int
$csizeOf :: RecordFlagBits -> Int
Storable, RecordFlagBits
RecordFlagBits -> Zero RecordFlagBits
forall a. a -> Zero a
zero :: RecordFlagBits
$czero :: RecordFlagBits
Zero, Eq RecordFlagBits
RecordFlagBits
Eq RecordFlagBits =>
(RecordFlagBits -> RecordFlagBits -> RecordFlagBits)
-> (RecordFlagBits -> RecordFlagBits -> RecordFlagBits)
-> (RecordFlagBits -> RecordFlagBits -> RecordFlagBits)
-> (RecordFlagBits -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> RecordFlagBits
-> (Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> Bool)
-> (RecordFlagBits -> Maybe Int)
-> (RecordFlagBits -> Int)
-> (RecordFlagBits -> Bool)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int -> RecordFlagBits)
-> (RecordFlagBits -> Int)
-> Bits RecordFlagBits
Int -> RecordFlagBits
RecordFlagBits -> Bool
RecordFlagBits -> Int
RecordFlagBits -> Maybe Int
RecordFlagBits -> RecordFlagBits
RecordFlagBits -> Int -> Bool
RecordFlagBits -> Int -> RecordFlagBits
RecordFlagBits -> RecordFlagBits -> RecordFlagBits
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: RecordFlagBits -> Int
$cpopCount :: RecordFlagBits -> Int
rotateR :: RecordFlagBits -> Int -> RecordFlagBits
$crotateR :: RecordFlagBits -> Int -> RecordFlagBits
rotateL :: RecordFlagBits -> Int -> RecordFlagBits
$crotateL :: RecordFlagBits -> Int -> RecordFlagBits
unsafeShiftR :: RecordFlagBits -> Int -> RecordFlagBits
$cunsafeShiftR :: RecordFlagBits -> Int -> RecordFlagBits
shiftR :: RecordFlagBits -> Int -> RecordFlagBits
$cshiftR :: RecordFlagBits -> Int -> RecordFlagBits
unsafeShiftL :: RecordFlagBits -> Int -> RecordFlagBits
$cunsafeShiftL :: RecordFlagBits -> Int -> RecordFlagBits
shiftL :: RecordFlagBits -> Int -> RecordFlagBits
$cshiftL :: RecordFlagBits -> Int -> RecordFlagBits
isSigned :: RecordFlagBits -> Bool
$cisSigned :: RecordFlagBits -> Bool
bitSize :: RecordFlagBits -> Int
$cbitSize :: RecordFlagBits -> Int
bitSizeMaybe :: RecordFlagBits -> Maybe Int
$cbitSizeMaybe :: RecordFlagBits -> Maybe Int
testBit :: RecordFlagBits -> Int -> Bool
$ctestBit :: RecordFlagBits -> Int -> Bool
complementBit :: RecordFlagBits -> Int -> RecordFlagBits
$ccomplementBit :: RecordFlagBits -> Int -> RecordFlagBits
clearBit :: RecordFlagBits -> Int -> RecordFlagBits
$cclearBit :: RecordFlagBits -> Int -> RecordFlagBits
setBit :: RecordFlagBits -> Int -> RecordFlagBits
$csetBit :: RecordFlagBits -> Int -> RecordFlagBits
bit :: Int -> RecordFlagBits
$cbit :: Int -> RecordFlagBits
zeroBits :: RecordFlagBits
$czeroBits :: RecordFlagBits
rotate :: RecordFlagBits -> Int -> RecordFlagBits
$crotate :: RecordFlagBits -> Int -> RecordFlagBits
shift :: RecordFlagBits -> Int -> RecordFlagBits
$cshift :: RecordFlagBits -> Int -> RecordFlagBits
complement :: RecordFlagBits -> RecordFlagBits
$ccomplement :: RecordFlagBits -> RecordFlagBits
xor :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
$cxor :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
.|. :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
$c.|. :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
.&. :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
$c.&. :: RecordFlagBits -> RecordFlagBits -> RecordFlagBits
$cp1Bits :: Eq RecordFlagBits
Bits)
pattern $bRECORD_FLUSH_AFTER_CALL_BIT :: RecordFlagBits
$mRECORD_FLUSH_AFTER_CALL_BIT :: forall r. RecordFlagBits -> (Void# -> r) -> (Void# -> r) -> r
RECORD_FLUSH_AFTER_CALL_BIT = RecordFlagBits 0x00000001
type RecordFlags = RecordFlagBits
instance Show RecordFlagBits where
showsPrec :: Int -> RecordFlagBits -> ShowS
showsPrec p :: Int
p = \case
RECORD_FLUSH_AFTER_CALL_BIT -> String -> ShowS
showString "RECORD_FLUSH_AFTER_CALL_BIT"
RecordFlagBits x :: "memoryTypeIndex" ::: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "RecordFlagBits 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("memoryTypeIndex" ::: Word32) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "memoryTypeIndex" ::: Word32
x)
instance Read RecordFlagBits where
readPrec :: ReadPrec RecordFlagBits
readPrec = ReadPrec RecordFlagBits -> ReadPrec RecordFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec RecordFlagBits)] -> ReadPrec RecordFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("RECORD_FLUSH_AFTER_CALL_BIT", RecordFlagBits -> ReadPrec RecordFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure RecordFlagBits
RECORD_FLUSH_AFTER_CALL_BIT)]
ReadPrec RecordFlagBits
-> ReadPrec RecordFlagBits -> ReadPrec RecordFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int -> ReadPrec RecordFlagBits -> ReadPrec RecordFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "RecordFlagBits")
"memoryTypeIndex" ::: Word32
v <- ReadPrec ("memoryTypeIndex" ::: Word32)
-> ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. Read a => ReadPrec a
readPrec
RecordFlagBits -> ReadPrec RecordFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("memoryTypeIndex" ::: Word32) -> RecordFlagBits
RecordFlagBits "memoryTypeIndex" ::: Word32
v)))
data RecordSettings = RecordSettings
{
RecordSettings -> RecordFlagBits
flags :: RecordFlags
,
RecordSettings -> ByteString
filePath :: ByteString
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (RecordSettings)
#endif
deriving instance Show RecordSettings
instance ToCStruct RecordSettings where
withCStruct :: RecordSettings -> (Ptr RecordSettings -> IO b) -> IO b
withCStruct x :: RecordSettings
x f :: Ptr RecordSettings -> IO b
f = Int -> Int -> (Ptr RecordSettings -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 8 ((Ptr RecordSettings -> IO b) -> IO b)
-> (Ptr RecordSettings -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr RecordSettings
p -> Ptr RecordSettings -> RecordSettings -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr RecordSettings
p RecordSettings
x (Ptr RecordSettings -> IO b
f Ptr RecordSettings
p)
pokeCStruct :: Ptr RecordSettings -> RecordSettings -> IO b -> IO b
pokeCStruct p :: Ptr RecordSettings
p RecordSettings{..} 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 RecordFlagBits -> RecordFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RecordSettings
p Ptr RecordSettings -> Int -> Ptr RecordFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr RecordFlags)) (RecordFlagBits
flags)
"statsString" ::: Ptr CChar
pFilePath'' <- ((("statsString" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("statsString" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("statsString" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("statsString" ::: Ptr CChar))
-> ((("statsString" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("statsString" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ByteString -> (("statsString" ::: Ptr CChar) -> IO b) -> IO b
forall a.
ByteString -> (("statsString" ::: Ptr CChar) -> IO a) -> IO a
useAsCString (ByteString
filePath)
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 ("statsString" ::: Ptr CChar)
-> ("statsString" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RecordSettings
p Ptr RecordSettings -> Int -> Ptr ("statsString" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr CChar))) "statsString" ::: Ptr CChar
pFilePath''
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 = 16
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr RecordSettings -> IO b -> IO b
pokeZeroCStruct p :: Ptr RecordSettings
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 RecordFlagBits -> RecordFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RecordSettings
p Ptr RecordSettings -> Int -> Ptr RecordFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr RecordFlags)) (RecordFlagBits
forall a. Zero a => a
zero)
"statsString" ::: Ptr CChar
pFilePath'' <- ((("statsString" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("statsString" ::: Ptr CChar)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((("statsString" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("statsString" ::: Ptr CChar))
-> ((("statsString" ::: Ptr CChar) -> IO b) -> IO b)
-> ContT b IO ("statsString" ::: Ptr CChar)
forall a b. (a -> b) -> a -> b
$ ByteString -> (("statsString" ::: Ptr CChar) -> IO b) -> IO b
forall a.
ByteString -> (("statsString" ::: Ptr CChar) -> IO a) -> IO a
useAsCString (ByteString
forall a. Monoid a => a
mempty)
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 ("statsString" ::: Ptr CChar)
-> ("statsString" ::: Ptr CChar) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr RecordSettings
p Ptr RecordSettings -> Int -> Ptr ("statsString" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr CChar))) "statsString" ::: Ptr CChar
pFilePath''
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 FromCStruct RecordSettings where
peekCStruct :: Ptr RecordSettings -> IO RecordSettings
peekCStruct p :: Ptr RecordSettings
p = do
RecordFlagBits
flags <- Ptr RecordFlagBits -> IO RecordFlagBits
forall a. Storable a => Ptr a -> IO a
peek @RecordFlags ((Ptr RecordSettings
p Ptr RecordSettings -> Int -> Ptr RecordFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr RecordFlags))
ByteString
pFilePath <- ("statsString" ::: Ptr CChar) -> IO ByteString
packCString (("statsString" ::: Ptr CChar) -> IO ByteString)
-> IO ("statsString" ::: Ptr CChar) -> IO ByteString
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Ptr ("statsString" ::: Ptr CChar)
-> IO ("statsString" ::: Ptr CChar)
forall a. Storable a => Ptr a -> IO a
peek ((Ptr RecordSettings
p Ptr RecordSettings -> Int -> Ptr ("statsString" ::: Ptr CChar)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr CChar)))
RecordSettings -> IO RecordSettings
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RecordSettings -> IO RecordSettings)
-> RecordSettings -> IO RecordSettings
forall a b. (a -> b) -> a -> b
$ RecordFlagBits -> ByteString -> RecordSettings
RecordSettings
RecordFlagBits
flags ByteString
pFilePath
instance Zero RecordSettings where
zero :: RecordSettings
zero = RecordFlagBits -> ByteString -> RecordSettings
RecordSettings
RecordFlagBits
forall a. Zero a => a
zero
ByteString
forall a. Monoid a => a
mempty
data AllocatorCreateInfo = AllocatorCreateInfo
{
AllocatorCreateInfo -> AllocatorCreateFlagBits
flags :: AllocatorCreateFlags
,
AllocatorCreateInfo -> Ptr PhysicalDevice_T
physicalDevice :: Ptr PhysicalDevice_T
,
AllocatorCreateInfo -> Ptr Device_T
device :: Ptr Device_T
,
AllocatorCreateInfo -> "lostAllocationCount" ::: Word64
preferredLargeHeapBlockSize :: DeviceSize
,
AllocatorCreateInfo -> Maybe AllocationCallbacks
allocationCallbacks :: Maybe AllocationCallbacks
,
AllocatorCreateInfo -> Maybe DeviceMemoryCallbacks
deviceMemoryCallbacks :: Maybe DeviceMemoryCallbacks
,
AllocatorCreateInfo -> "memoryTypeIndex" ::: Word32
frameInUseCount :: Word32
,
AllocatorCreateInfo -> Ptr ("lostAllocationCount" ::: Word64)
heapSizeLimit :: Ptr DeviceSize
,
AllocatorCreateInfo -> Maybe VulkanFunctions
vulkanFunctions :: Maybe VulkanFunctions
,
AllocatorCreateInfo -> Maybe RecordSettings
recordSettings :: Maybe RecordSettings
,
AllocatorCreateInfo -> Ptr Instance_T
instance' :: Ptr Instance_T
,
AllocatorCreateInfo -> "memoryTypeIndex" ::: Word32
vulkanApiVersion :: Word32
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AllocatorCreateInfo)
#endif
deriving instance Show AllocatorCreateInfo
instance ToCStruct AllocatorCreateInfo where
withCStruct :: AllocatorCreateInfo -> (Ptr AllocatorCreateInfo -> IO b) -> IO b
withCStruct x :: AllocatorCreateInfo
x f :: Ptr AllocatorCreateInfo -> IO b
f = Int -> Int -> (Ptr AllocatorCreateInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 96 8 ((Ptr AllocatorCreateInfo -> IO b) -> IO b)
-> (Ptr AllocatorCreateInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AllocatorCreateInfo
p -> Ptr AllocatorCreateInfo -> AllocatorCreateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AllocatorCreateInfo
p AllocatorCreateInfo
x (Ptr AllocatorCreateInfo -> IO b
f Ptr AllocatorCreateInfo
p)
pokeCStruct :: Ptr AllocatorCreateInfo -> AllocatorCreateInfo -> IO b -> IO b
pokeCStruct p :: Ptr AllocatorCreateInfo
p AllocatorCreateInfo{..} 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 AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr AllocatorCreateFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr AllocatorCreateFlags)) (AllocatorCreateFlagBits
flags)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr PhysicalDevice_T) -> Ptr PhysicalDevice_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr PhysicalDevice_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr PhysicalDevice_T))) (Ptr PhysicalDevice_T
physicalDevice)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Device_T) -> Ptr Device_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr Device_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr Device_T))) (Ptr Device_T
device)
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 ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
preferredLargeHeapBlockSize)
Ptr AllocationCallbacks
pAllocationCallbacks'' <- case (Maybe AllocationCallbacks
allocationCallbacks) of
Nothing -> Ptr AllocationCallbacks -> ContT b IO (Ptr AllocationCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr AllocationCallbacks
forall a. Ptr a
nullPtr
Just j :: AllocationCallbacks
j -> ((Ptr AllocationCallbacks -> IO b) -> IO b)
-> ContT b IO (Ptr AllocationCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr AllocationCallbacks -> IO b) -> IO b)
-> ContT b IO (Ptr AllocationCallbacks))
-> ((Ptr AllocationCallbacks -> IO b) -> IO b)
-> ContT b IO (Ptr AllocationCallbacks)
forall a b. (a -> b) -> a -> b
$ AllocationCallbacks -> (Ptr AllocationCallbacks -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (AllocationCallbacks
j)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr AllocationCallbacks) -> Ptr AllocationCallbacks -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr AllocationCallbacks)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr AllocationCallbacks))) Ptr AllocationCallbacks
pAllocationCallbacks''
Ptr DeviceMemoryCallbacks
pDeviceMemoryCallbacks'' <- case (Maybe DeviceMemoryCallbacks
deviceMemoryCallbacks) of
Nothing -> Ptr DeviceMemoryCallbacks -> ContT b IO (Ptr DeviceMemoryCallbacks)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr DeviceMemoryCallbacks
forall a. Ptr a
nullPtr
Just j :: DeviceMemoryCallbacks
j -> ((Ptr DeviceMemoryCallbacks -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemoryCallbacks)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr DeviceMemoryCallbacks -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemoryCallbacks))
-> ((Ptr DeviceMemoryCallbacks -> IO b) -> IO b)
-> ContT b IO (Ptr DeviceMemoryCallbacks)
forall a b. (a -> b) -> a -> b
$ DeviceMemoryCallbacks
-> (Ptr DeviceMemoryCallbacks -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (DeviceMemoryCallbacks
j)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr DeviceMemoryCallbacks)
-> Ptr DeviceMemoryCallbacks -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr DeviceMemoryCallbacks)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr DeviceMemoryCallbacks))) Ptr DeviceMemoryCallbacks
pDeviceMemoryCallbacks''
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 ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
frameInUseCount)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr ("lostAllocationCount" ::: Word64))
-> Ptr ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr (Ptr ("lostAllocationCount" ::: Word64))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr DeviceSize))) (Ptr ("lostAllocationCount" ::: Word64)
heapSizeLimit)
Ptr VulkanFunctions
pVulkanFunctions'' <- case (Maybe VulkanFunctions
vulkanFunctions) of
Nothing -> Ptr VulkanFunctions -> ContT b IO (Ptr VulkanFunctions)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr VulkanFunctions
forall a. Ptr a
nullPtr
Just j :: VulkanFunctions
j -> ((Ptr VulkanFunctions -> IO b) -> IO b)
-> ContT b IO (Ptr VulkanFunctions)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr VulkanFunctions -> IO b) -> IO b)
-> ContT b IO (Ptr VulkanFunctions))
-> ((Ptr VulkanFunctions -> IO b) -> IO b)
-> ContT b IO (Ptr VulkanFunctions)
forall a b. (a -> b) -> a -> b
$ VulkanFunctions -> (Ptr VulkanFunctions -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (VulkanFunctions
j)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr VulkanFunctions) -> Ptr VulkanFunctions -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr VulkanFunctions)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr VulkanFunctions))) Ptr VulkanFunctions
pVulkanFunctions''
Ptr RecordSettings
pRecordSettings'' <- case (Maybe RecordSettings
recordSettings) of
Nothing -> Ptr RecordSettings -> ContT b IO (Ptr RecordSettings)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Ptr RecordSettings
forall a. Ptr a
nullPtr
Just j :: RecordSettings
j -> ((Ptr RecordSettings -> IO b) -> IO b)
-> ContT b IO (Ptr RecordSettings)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr RecordSettings -> IO b) -> IO b)
-> ContT b IO (Ptr RecordSettings))
-> ((Ptr RecordSettings -> IO b) -> IO b)
-> ContT b IO (Ptr RecordSettings)
forall a b. (a -> b) -> a -> b
$ RecordSettings -> (Ptr RecordSettings -> IO b) -> IO b
forall a b. ToCStruct a => a -> (Ptr a -> IO b) -> IO b
withCStruct (RecordSettings
j)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr RecordSettings) -> Ptr RecordSettings -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr RecordSettings)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr RecordSettings))) Ptr RecordSettings
pRecordSettings''
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Instance_T) -> Ptr Instance_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr Instance_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr (Ptr Instance_T))) (Ptr Instance_T
instance')
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 ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
vulkanApiVersion)
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 = 96
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr AllocatorCreateInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr AllocatorCreateInfo
p f :: IO b
f = do
Ptr AllocatorCreateFlagBits -> AllocatorCreateFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr AllocatorCreateFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr AllocatorCreateFlags)) (AllocatorCreateFlagBits
forall a. Zero a => a
zero)
Ptr (Ptr PhysicalDevice_T) -> Ptr PhysicalDevice_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr PhysicalDevice_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr PhysicalDevice_T))) (Ptr PhysicalDevice_T
forall a. Zero a => a
zero)
Ptr (Ptr Device_T) -> Ptr Device_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr Device_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr Device_T))) (Ptr Device_T
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
Ptr (Ptr Instance_T) -> Ptr Instance_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr Instance_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr (Ptr Instance_T))) (Ptr Instance_T
forall a. Zero a => a
zero)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct AllocatorCreateInfo where
peekCStruct :: Ptr AllocatorCreateInfo -> IO AllocatorCreateInfo
peekCStruct p :: Ptr AllocatorCreateInfo
p = do
AllocatorCreateFlagBits
flags <- Ptr AllocatorCreateFlagBits -> IO AllocatorCreateFlagBits
forall a. Storable a => Ptr a -> IO a
peek @AllocatorCreateFlags ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr AllocatorCreateFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr AllocatorCreateFlags))
Ptr PhysicalDevice_T
physicalDevice <- Ptr (Ptr PhysicalDevice_T) -> IO (Ptr PhysicalDevice_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PhysicalDevice_T) ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr PhysicalDevice_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr PhysicalDevice_T)))
Ptr Device_T
device <- Ptr (Ptr Device_T) -> IO (Ptr Device_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Device_T) ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr Device_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr Device_T)))
"lostAllocationCount" ::: Word64
preferredLargeHeapBlockSize <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
Ptr AllocationCallbacks
pAllocationCallbacks <- Ptr (Ptr AllocationCallbacks) -> IO (Ptr AllocationCallbacks)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr AllocationCallbacks) ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr AllocationCallbacks)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr AllocationCallbacks)))
Maybe AllocationCallbacks
pAllocationCallbacks' <- (Ptr AllocationCallbacks -> IO AllocationCallbacks)
-> Ptr AllocationCallbacks -> IO (Maybe AllocationCallbacks)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr AllocationCallbacks
j -> Ptr AllocationCallbacks -> IO AllocationCallbacks
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @AllocationCallbacks (Ptr AllocationCallbacks
j)) Ptr AllocationCallbacks
pAllocationCallbacks
Ptr DeviceMemoryCallbacks
pDeviceMemoryCallbacks <- Ptr (Ptr DeviceMemoryCallbacks) -> IO (Ptr DeviceMemoryCallbacks)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr DeviceMemoryCallbacks) ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr DeviceMemoryCallbacks)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr DeviceMemoryCallbacks)))
Maybe DeviceMemoryCallbacks
pDeviceMemoryCallbacks' <- (Ptr DeviceMemoryCallbacks -> IO DeviceMemoryCallbacks)
-> Ptr DeviceMemoryCallbacks -> IO (Maybe DeviceMemoryCallbacks)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr DeviceMemoryCallbacks
j -> Ptr DeviceMemoryCallbacks -> IO DeviceMemoryCallbacks
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @DeviceMemoryCallbacks (Ptr DeviceMemoryCallbacks
j)) Ptr DeviceMemoryCallbacks
pDeviceMemoryCallbacks
"memoryTypeIndex" ::: Word32
frameInUseCount <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
Ptr ("lostAllocationCount" ::: Word64)
pHeapSizeLimit <- Ptr (Ptr ("lostAllocationCount" ::: Word64))
-> IO (Ptr ("lostAllocationCount" ::: Word64))
forall a. Storable a => Ptr a -> IO a
peek @(Ptr DeviceSize) ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr (Ptr ("lostAllocationCount" ::: Word64))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr (Ptr DeviceSize)))
Ptr VulkanFunctions
pVulkanFunctions <- Ptr (Ptr VulkanFunctions) -> IO (Ptr VulkanFunctions)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr VulkanFunctions) ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr VulkanFunctions)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr (Ptr VulkanFunctions)))
Maybe VulkanFunctions
pVulkanFunctions' <- (Ptr VulkanFunctions -> IO VulkanFunctions)
-> Ptr VulkanFunctions -> IO (Maybe VulkanFunctions)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr VulkanFunctions
j -> Ptr VulkanFunctions -> IO VulkanFunctions
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @VulkanFunctions (Ptr VulkanFunctions
j)) Ptr VulkanFunctions
pVulkanFunctions
Ptr RecordSettings
pRecordSettings <- Ptr (Ptr RecordSettings) -> IO (Ptr RecordSettings)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr RecordSettings) ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr RecordSettings)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr RecordSettings)))
Maybe RecordSettings
pRecordSettings' <- (Ptr RecordSettings -> IO RecordSettings)
-> Ptr RecordSettings -> IO (Maybe RecordSettings)
forall a b. (Ptr a -> IO b) -> Ptr a -> IO (Maybe b)
maybePeek (\j :: Ptr RecordSettings
j -> Ptr RecordSettings -> IO RecordSettings
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @RecordSettings (Ptr RecordSettings
j)) Ptr RecordSettings
pRecordSettings
Ptr Instance_T
instance' <- Ptr (Ptr Instance_T) -> IO (Ptr Instance_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Instance_T) ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo -> Int -> Ptr (Ptr Instance_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 80 :: Ptr (Ptr Instance_T)))
"memoryTypeIndex" ::: Word32
vulkanApiVersion <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AllocatorCreateInfo
p Ptr AllocatorCreateInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 88 :: Ptr Word32))
AllocatorCreateInfo -> IO AllocatorCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AllocatorCreateInfo -> IO AllocatorCreateInfo)
-> AllocatorCreateInfo -> IO AllocatorCreateInfo
forall a b. (a -> b) -> a -> b
$ AllocatorCreateFlagBits
-> Ptr PhysicalDevice_T
-> Ptr Device_T
-> ("lostAllocationCount" ::: Word64)
-> Maybe AllocationCallbacks
-> Maybe DeviceMemoryCallbacks
-> ("memoryTypeIndex" ::: Word32)
-> Ptr ("lostAllocationCount" ::: Word64)
-> Maybe VulkanFunctions
-> Maybe RecordSettings
-> Ptr Instance_T
-> ("memoryTypeIndex" ::: Word32)
-> AllocatorCreateInfo
AllocatorCreateInfo
AllocatorCreateFlagBits
flags Ptr PhysicalDevice_T
physicalDevice Ptr Device_T
device "lostAllocationCount" ::: Word64
preferredLargeHeapBlockSize Maybe AllocationCallbacks
pAllocationCallbacks' Maybe DeviceMemoryCallbacks
pDeviceMemoryCallbacks' "memoryTypeIndex" ::: Word32
frameInUseCount Ptr ("lostAllocationCount" ::: Word64)
pHeapSizeLimit Maybe VulkanFunctions
pVulkanFunctions' Maybe RecordSettings
pRecordSettings' Ptr Instance_T
instance' "memoryTypeIndex" ::: Word32
vulkanApiVersion
instance Zero AllocatorCreateInfo where
zero :: AllocatorCreateInfo
zero = AllocatorCreateFlagBits
-> Ptr PhysicalDevice_T
-> Ptr Device_T
-> ("lostAllocationCount" ::: Word64)
-> Maybe AllocationCallbacks
-> Maybe DeviceMemoryCallbacks
-> ("memoryTypeIndex" ::: Word32)
-> Ptr ("lostAllocationCount" ::: Word64)
-> Maybe VulkanFunctions
-> Maybe RecordSettings
-> Ptr Instance_T
-> ("memoryTypeIndex" ::: Word32)
-> AllocatorCreateInfo
AllocatorCreateInfo
AllocatorCreateFlagBits
forall a. Zero a => a
zero
Ptr PhysicalDevice_T
forall a. Zero a => a
zero
Ptr Device_T
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
Maybe AllocationCallbacks
forall a. Maybe a
Nothing
Maybe DeviceMemoryCallbacks
forall a. Maybe a
Nothing
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
Ptr ("lostAllocationCount" ::: Word64)
forall a. Zero a => a
zero
Maybe VulkanFunctions
forall a. Maybe a
Nothing
Maybe RecordSettings
forall a. Maybe a
Nothing
Ptr Instance_T
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
data AllocatorInfo = AllocatorInfo
{
AllocatorInfo -> Ptr Instance_T
instance' :: Ptr Instance_T
,
AllocatorInfo -> Ptr PhysicalDevice_T
physicalDevice :: Ptr PhysicalDevice_T
,
AllocatorInfo -> Ptr Device_T
device :: Ptr Device_T
}
deriving (Typeable, AllocatorInfo -> AllocatorInfo -> Bool
(AllocatorInfo -> AllocatorInfo -> Bool)
-> (AllocatorInfo -> AllocatorInfo -> Bool) -> Eq AllocatorInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AllocatorInfo -> AllocatorInfo -> Bool
$c/= :: AllocatorInfo -> AllocatorInfo -> Bool
== :: AllocatorInfo -> AllocatorInfo -> Bool
$c== :: AllocatorInfo -> AllocatorInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AllocatorInfo)
#endif
deriving instance Show AllocatorInfo
instance ToCStruct AllocatorInfo where
withCStruct :: AllocatorInfo -> (Ptr AllocatorInfo -> IO b) -> IO b
withCStruct x :: AllocatorInfo
x f :: Ptr AllocatorInfo -> IO b
f = Int -> Int -> (Ptr AllocatorInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr AllocatorInfo -> IO b) -> IO b)
-> (Ptr AllocatorInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AllocatorInfo
p -> Ptr AllocatorInfo -> AllocatorInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AllocatorInfo
p AllocatorInfo
x (Ptr AllocatorInfo -> IO b
f Ptr AllocatorInfo
p)
pokeCStruct :: Ptr AllocatorInfo -> AllocatorInfo -> IO b -> IO b
pokeCStruct p :: Ptr AllocatorInfo
p AllocatorInfo{..} f :: IO b
f = do
Ptr (Ptr Instance_T) -> Ptr Instance_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorInfo
p Ptr AllocatorInfo -> Int -> Ptr (Ptr Instance_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr (Ptr Instance_T))) (Ptr Instance_T
instance')
Ptr (Ptr PhysicalDevice_T) -> Ptr PhysicalDevice_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorInfo
p Ptr AllocatorInfo -> Int -> Ptr (Ptr PhysicalDevice_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr PhysicalDevice_T))) (Ptr PhysicalDevice_T
physicalDevice)
Ptr (Ptr Device_T) -> Ptr Device_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorInfo
p Ptr AllocatorInfo -> Int -> Ptr (Ptr Device_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr Device_T))) (Ptr Device_T
device)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr AllocatorInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr AllocatorInfo
p f :: IO b
f = do
Ptr (Ptr Instance_T) -> Ptr Instance_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorInfo
p Ptr AllocatorInfo -> Int -> Ptr (Ptr Instance_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr (Ptr Instance_T))) (Ptr Instance_T
forall a. Zero a => a
zero)
Ptr (Ptr PhysicalDevice_T) -> Ptr PhysicalDevice_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorInfo
p Ptr AllocatorInfo -> Int -> Ptr (Ptr PhysicalDevice_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr PhysicalDevice_T))) (Ptr PhysicalDevice_T
forall a. Zero a => a
zero)
Ptr (Ptr Device_T) -> Ptr Device_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocatorInfo
p Ptr AllocatorInfo -> Int -> Ptr (Ptr Device_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr Device_T))) (Ptr Device_T
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct AllocatorInfo where
peekCStruct :: Ptr AllocatorInfo -> IO AllocatorInfo
peekCStruct p :: Ptr AllocatorInfo
p = do
Ptr Instance_T
instance' <- Ptr (Ptr Instance_T) -> IO (Ptr Instance_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Instance_T) ((Ptr AllocatorInfo
p Ptr AllocatorInfo -> Int -> Ptr (Ptr Instance_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr (Ptr Instance_T)))
Ptr PhysicalDevice_T
physicalDevice <- Ptr (Ptr PhysicalDevice_T) -> IO (Ptr PhysicalDevice_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr PhysicalDevice_T) ((Ptr AllocatorInfo
p Ptr AllocatorInfo -> Int -> Ptr (Ptr PhysicalDevice_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr PhysicalDevice_T)))
Ptr Device_T
device <- Ptr (Ptr Device_T) -> IO (Ptr Device_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Device_T) ((Ptr AllocatorInfo
p Ptr AllocatorInfo -> Int -> Ptr (Ptr Device_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr Device_T)))
AllocatorInfo -> IO AllocatorInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AllocatorInfo -> IO AllocatorInfo)
-> AllocatorInfo -> IO AllocatorInfo
forall a b. (a -> b) -> a -> b
$ Ptr Instance_T
-> Ptr PhysicalDevice_T -> Ptr Device_T -> AllocatorInfo
AllocatorInfo
Ptr Instance_T
instance' Ptr PhysicalDevice_T
physicalDevice Ptr Device_T
device
instance Storable AllocatorInfo where
sizeOf :: AllocatorInfo -> Int
sizeOf ~AllocatorInfo
_ = 24
alignment :: AllocatorInfo -> Int
alignment ~AllocatorInfo
_ = 8
peek :: Ptr AllocatorInfo -> IO AllocatorInfo
peek = Ptr AllocatorInfo -> IO AllocatorInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr AllocatorInfo -> AllocatorInfo -> IO ()
poke ptr :: Ptr AllocatorInfo
ptr poked :: AllocatorInfo
poked = Ptr AllocatorInfo -> AllocatorInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AllocatorInfo
ptr AllocatorInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero AllocatorInfo where
zero :: AllocatorInfo
zero = Ptr Instance_T
-> Ptr PhysicalDevice_T -> Ptr Device_T -> AllocatorInfo
AllocatorInfo
Ptr Instance_T
forall a. Zero a => a
zero
Ptr PhysicalDevice_T
forall a. Zero a => a
zero
Ptr Device_T
forall a. Zero a => a
zero
data StatInfo = StatInfo
{
StatInfo -> "memoryTypeIndex" ::: Word32
blockCount :: Word32
,
StatInfo -> "memoryTypeIndex" ::: Word32
allocationCount :: Word32
,
StatInfo -> "memoryTypeIndex" ::: Word32
unusedRangeCount :: Word32
,
StatInfo -> "lostAllocationCount" ::: Word64
usedBytes :: DeviceSize
,
StatInfo -> "lostAllocationCount" ::: Word64
unusedBytes :: DeviceSize
,
StatInfo -> "lostAllocationCount" ::: Word64
allocationSizeMin :: DeviceSize
,
StatInfo -> "lostAllocationCount" ::: Word64
allocationSizeAvg :: DeviceSize
,
StatInfo -> "lostAllocationCount" ::: Word64
allocationSizeMax :: DeviceSize
,
StatInfo -> "lostAllocationCount" ::: Word64
unusedRangeSizeMin :: DeviceSize
,
StatInfo -> "lostAllocationCount" ::: Word64
unusedRangeSizeAvg :: DeviceSize
,
StatInfo -> "lostAllocationCount" ::: Word64
unusedRangeSizeMax :: DeviceSize
}
deriving (Typeable, StatInfo -> StatInfo -> Bool
(StatInfo -> StatInfo -> Bool)
-> (StatInfo -> StatInfo -> Bool) -> Eq StatInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatInfo -> StatInfo -> Bool
$c/= :: StatInfo -> StatInfo -> Bool
== :: StatInfo -> StatInfo -> Bool
$c== :: StatInfo -> StatInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (StatInfo)
#endif
deriving instance Show StatInfo
instance ToCStruct StatInfo where
withCStruct :: StatInfo -> (Ptr StatInfo -> IO b) -> IO b
withCStruct x :: StatInfo
x f :: Ptr StatInfo -> IO b
f = Int -> Int -> (Ptr StatInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 80 8 ((Ptr StatInfo -> IO b) -> IO b) -> (Ptr StatInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr StatInfo
p -> Ptr StatInfo -> StatInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr StatInfo
p StatInfo
x (Ptr StatInfo -> IO b
f Ptr StatInfo
p)
pokeCStruct :: Ptr StatInfo -> StatInfo -> IO b -> IO b
pokeCStruct p :: Ptr StatInfo
p StatInfo{..} f :: IO b
f = do
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
blockCount)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
allocationCount)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
unusedRangeCount)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
usedBytes)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
unusedBytes)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
allocationSizeMin)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
allocationSizeAvg)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
allocationSizeMax)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
unusedRangeSizeMin)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
unusedRangeSizeAvg)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
unusedRangeSizeMax)
IO b
f
cStructSize :: Int
cStructSize = 80
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr StatInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr StatInfo
p f :: IO b
f = do
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct StatInfo where
peekCStruct :: Ptr StatInfo -> IO StatInfo
peekCStruct p :: Ptr StatInfo
p = do
"memoryTypeIndex" ::: Word32
blockCount <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
"memoryTypeIndex" ::: Word32
allocationCount <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
"memoryTypeIndex" ::: Word32
unusedRangeCount <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
"lostAllocationCount" ::: Word64
usedBytes <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
unusedBytes <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
allocationSizeMin <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
allocationSizeAvg <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
allocationSizeMax <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
unusedRangeSizeMin <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
unusedRangeSizeAvg <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
unusedRangeSizeMax <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr StatInfo
p Ptr StatInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr DeviceSize))
StatInfo -> IO StatInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (StatInfo -> IO StatInfo) -> StatInfo -> IO StatInfo
forall a b. (a -> b) -> a -> b
$ ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> StatInfo
StatInfo
"memoryTypeIndex" ::: Word32
blockCount "memoryTypeIndex" ::: Word32
allocationCount "memoryTypeIndex" ::: Word32
unusedRangeCount "lostAllocationCount" ::: Word64
usedBytes "lostAllocationCount" ::: Word64
unusedBytes "lostAllocationCount" ::: Word64
allocationSizeMin "lostAllocationCount" ::: Word64
allocationSizeAvg "lostAllocationCount" ::: Word64
allocationSizeMax "lostAllocationCount" ::: Word64
unusedRangeSizeMin "lostAllocationCount" ::: Word64
unusedRangeSizeAvg "lostAllocationCount" ::: Word64
unusedRangeSizeMax
instance Storable StatInfo where
sizeOf :: StatInfo -> Int
sizeOf ~StatInfo
_ = 80
alignment :: StatInfo -> Int
alignment ~StatInfo
_ = 8
peek :: Ptr StatInfo -> IO StatInfo
peek = Ptr StatInfo -> IO StatInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr StatInfo -> StatInfo -> IO ()
poke ptr :: Ptr StatInfo
ptr poked :: StatInfo
poked = Ptr StatInfo -> StatInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr StatInfo
ptr StatInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero StatInfo where
zero :: StatInfo
zero = ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> StatInfo
StatInfo
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
data Stats = Stats
{
Stats -> Vector StatInfo
memoryType :: Vector StatInfo
,
Stats -> Vector StatInfo
memoryHeap :: Vector StatInfo
,
Stats -> StatInfo
total :: StatInfo
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (Stats)
#endif
deriving instance Show Stats
instance ToCStruct Stats where
withCStruct :: Stats -> (Ptr Stats -> IO b) -> IO b
withCStruct x :: Stats
x f :: Ptr Stats -> IO b
f = Int -> Int -> (Ptr Stats -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 3920 8 ((Ptr Stats -> IO b) -> IO b) -> (Ptr Stats -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr Stats
p -> Ptr Stats -> Stats -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Stats
p Stats
x (Ptr Stats -> IO b
f Ptr Stats
p)
pokeCStruct :: Ptr Stats -> Stats -> IO b -> IO b
pokeCStruct p :: Ptr Stats
p Stats{..} f :: IO b
f = do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector StatInfo -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector StatInfo -> Int) -> Vector StatInfo -> Int
forall a b. (a -> b) -> a -> b
$ (Vector StatInfo
memoryType)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_TYPES) (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 "" "memoryType is too long, a maximum of MAX_MEMORY_TYPES elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
(Int -> StatInfo -> IO ()) -> Vector StatInfo -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: StatInfo
e -> Ptr StatInfo -> StatInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_MEMORY_TYPES StatInfo) -> Ptr StatInfo
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr Stats
p Ptr Stats -> Int -> Ptr (FixedArray MAX_MEMORY_TYPES StatInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr (FixedArray MAX_MEMORY_TYPES StatInfo)))) Ptr StatInfo -> Int -> Ptr StatInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (80 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr StatInfo) (StatInfo
e)) (Vector StatInfo
memoryType)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector StatInfo -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector StatInfo -> Int) -> Vector StatInfo -> Int
forall a b. (a -> b) -> a -> b
$ (Vector StatInfo
memoryHeap)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (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 "" "memoryHeap is too long, a maximum of MAX_MEMORY_HEAPS elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
(Int -> StatInfo -> IO ()) -> Vector StatInfo -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: StatInfo
e -> Ptr StatInfo -> StatInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_MEMORY_HEAPS StatInfo) -> Ptr StatInfo
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr Stats
p Ptr Stats -> Int -> Ptr (FixedArray MAX_MEMORY_HEAPS StatInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 2560 :: Ptr (FixedArray MAX_MEMORY_HEAPS StatInfo)))) Ptr StatInfo -> Int -> Ptr StatInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (80 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr StatInfo) (StatInfo
e)) (Vector StatInfo
memoryHeap)
Ptr StatInfo -> StatInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Stats
p Ptr Stats -> Int -> Ptr StatInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 3840 :: Ptr StatInfo)) (StatInfo
total)
IO b
f
cStructSize :: Int
cStructSize = 3920
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr Stats -> IO b -> IO b
pokeZeroCStruct p :: Ptr Stats
p f :: IO b
f = do
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any -> Int) -> Vector Any -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_TYPES) (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 "" "memoryType is too long, a maximum of MAX_MEMORY_TYPES elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
(Int -> StatInfo -> IO ()) -> Vector StatInfo -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: StatInfo
e -> Ptr StatInfo -> StatInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_MEMORY_TYPES StatInfo) -> Ptr StatInfo
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr Stats
p Ptr Stats -> Int -> Ptr (FixedArray MAX_MEMORY_TYPES StatInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr (FixedArray MAX_MEMORY_TYPES StatInfo)))) Ptr StatInfo -> Int -> Ptr StatInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (80 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr StatInfo) (StatInfo
e)) (Vector StatInfo
forall a. Monoid a => a
mempty)
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any -> Int) -> Vector Any -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (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 "" "memoryHeap is too long, a maximum of MAX_MEMORY_HEAPS elements are allowed" Maybe CInt
forall a. Maybe a
Nothing Maybe String
forall a. Maybe a
Nothing
(Int -> StatInfo -> IO ()) -> Vector StatInfo -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: StatInfo
e -> Ptr StatInfo -> StatInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr (FixedArray MAX_MEMORY_HEAPS StatInfo) -> Ptr StatInfo
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr ((Ptr Stats
p Ptr Stats -> Int -> Ptr (FixedArray MAX_MEMORY_HEAPS StatInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 2560 :: Ptr (FixedArray MAX_MEMORY_HEAPS StatInfo)))) Ptr StatInfo -> Int -> Ptr StatInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (80 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr StatInfo) (StatInfo
e)) (Vector StatInfo
forall a. Monoid a => a
mempty)
Ptr StatInfo -> StatInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Stats
p Ptr Stats -> Int -> Ptr StatInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 3840 :: Ptr StatInfo)) (StatInfo
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct Stats where
peekCStruct :: Ptr Stats -> IO Stats
peekCStruct p :: Ptr Stats
p = do
Vector StatInfo
memoryType <- Int -> (Int -> IO StatInfo) -> IO (Vector StatInfo)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Int
forall a. Integral a => a
MAX_MEMORY_TYPES) (\i :: Int
i -> Ptr StatInfo -> IO StatInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @StatInfo (((Ptr (FixedArray MAX_MEMORY_TYPES StatInfo) -> Ptr StatInfo
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @StatInfo ((Ptr Stats
p Ptr Stats -> Int -> Ptr (FixedArray MAX_MEMORY_TYPES StatInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr (FixedArray MAX_MEMORY_TYPES StatInfo)))) Ptr StatInfo -> Int -> Ptr StatInfo
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (80 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr StatInfo)))
Vector StatInfo
memoryHeap <- Int -> (Int -> IO StatInfo) -> IO (Vector StatInfo)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (Int
forall a. Integral a => a
MAX_MEMORY_HEAPS) (\i :: Int
i -> Ptr StatInfo -> IO StatInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @StatInfo (((Ptr (FixedArray MAX_MEMORY_HEAPS StatInfo) -> Ptr StatInfo
forall a (n :: Nat). Ptr (FixedArray n a) -> Ptr a
lowerArrayPtr @StatInfo ((Ptr Stats
p Ptr Stats -> Int -> Ptr (FixedArray MAX_MEMORY_HEAPS StatInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 2560 :: Ptr (FixedArray MAX_MEMORY_HEAPS StatInfo)))) Ptr StatInfo -> Int -> Ptr StatInfo
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (80 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr StatInfo)))
StatInfo
total <- Ptr StatInfo -> IO StatInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct @StatInfo ((Ptr Stats
p Ptr Stats -> Int -> Ptr StatInfo
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 3840 :: Ptr StatInfo))
Stats -> IO Stats
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Stats -> IO Stats) -> Stats -> IO Stats
forall a b. (a -> b) -> a -> b
$ Vector StatInfo -> Vector StatInfo -> StatInfo -> Stats
Stats
Vector StatInfo
memoryType Vector StatInfo
memoryHeap StatInfo
total
instance Storable Stats where
sizeOf :: Stats -> Int
sizeOf ~Stats
_ = 3920
alignment :: Stats -> Int
alignment ~Stats
_ = 8
peek :: Ptr Stats -> IO Stats
peek = Ptr Stats -> IO Stats
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr Stats -> Stats -> IO ()
poke ptr :: Ptr Stats
ptr poked :: Stats
poked = Ptr Stats -> Stats -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Stats
ptr Stats
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero Stats where
zero :: Stats
zero = Vector StatInfo -> Vector StatInfo -> StatInfo -> Stats
Stats
Vector StatInfo
forall a. Monoid a => a
mempty
Vector StatInfo
forall a. Monoid a => a
mempty
StatInfo
forall a. Zero a => a
zero
data Budget = Budget
{
Budget -> "lostAllocationCount" ::: Word64
blockBytes :: DeviceSize
,
Budget -> "lostAllocationCount" ::: Word64
allocationBytes :: DeviceSize
,
Budget -> "lostAllocationCount" ::: Word64
usage :: DeviceSize
,
Budget -> "lostAllocationCount" ::: Word64
budget :: DeviceSize
}
deriving (Typeable, Budget -> Budget -> Bool
(Budget -> Budget -> Bool)
-> (Budget -> Budget -> Bool) -> Eq Budget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Budget -> Budget -> Bool
$c/= :: Budget -> Budget -> Bool
== :: Budget -> Budget -> Bool
$c== :: Budget -> Budget -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (Budget)
#endif
deriving instance Show Budget
instance ToCStruct Budget where
withCStruct :: Budget -> (Ptr Budget -> IO b) -> IO b
withCStruct x :: Budget
x f :: Ptr Budget -> IO b
f = Int -> Int -> (Ptr Budget -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 32 8 ((Ptr Budget -> IO b) -> IO b) -> (Ptr Budget -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr Budget
p -> Ptr Budget -> Budget -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Budget
p Budget
x (Ptr Budget -> IO b
f Ptr Budget
p)
pokeCStruct :: Ptr Budget -> Budget -> IO b -> IO b
pokeCStruct p :: Ptr Budget
p Budget{..} f :: IO b
f = do
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
blockBytes)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
allocationBytes)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
usage)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
budget)
IO b
f
cStructSize :: Int
cStructSize = 32
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr Budget -> IO b -> IO b
pokeZeroCStruct p :: Ptr Budget
p f :: IO b
f = do
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct Budget where
peekCStruct :: Ptr Budget -> IO Budget
peekCStruct p :: Ptr Budget
p = do
"lostAllocationCount" ::: Word64
blockBytes <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
allocationBytes <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
usage <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
budget <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr Budget
p Ptr Budget -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
Budget -> IO Budget
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Budget -> IO Budget) -> Budget -> IO Budget
forall a b. (a -> b) -> a -> b
$ ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> Budget
Budget
"lostAllocationCount" ::: Word64
blockBytes "lostAllocationCount" ::: Word64
allocationBytes "lostAllocationCount" ::: Word64
usage "lostAllocationCount" ::: Word64
budget
instance Storable Budget where
sizeOf :: Budget -> Int
sizeOf ~Budget
_ = 32
alignment :: Budget -> Int
alignment ~Budget
_ = 8
peek :: Ptr Budget -> IO Budget
peek = Ptr Budget -> IO Budget
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr Budget -> Budget -> IO ()
poke ptr :: Ptr Budget
ptr poked :: Budget
poked = Ptr Budget -> Budget -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr Budget
ptr Budget
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero Budget where
zero :: Budget
zero = ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> Budget
Budget
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
newtype Pool = Pool Word64
deriving newtype (Pool -> Pool -> Bool
(Pool -> Pool -> Bool) -> (Pool -> Pool -> Bool) -> Eq Pool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Pool -> Pool -> Bool
$c/= :: Pool -> Pool -> Bool
== :: Pool -> Pool -> Bool
$c== :: Pool -> Pool -> Bool
Eq, Eq Pool
Eq Pool =>
(Pool -> Pool -> Ordering)
-> (Pool -> Pool -> Bool)
-> (Pool -> Pool -> Bool)
-> (Pool -> Pool -> Bool)
-> (Pool -> Pool -> Bool)
-> (Pool -> Pool -> Pool)
-> (Pool -> Pool -> Pool)
-> Ord Pool
Pool -> Pool -> Bool
Pool -> Pool -> Ordering
Pool -> Pool -> Pool
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Pool -> Pool -> Pool
$cmin :: Pool -> Pool -> Pool
max :: Pool -> Pool -> Pool
$cmax :: Pool -> Pool -> Pool
>= :: Pool -> Pool -> Bool
$c>= :: Pool -> Pool -> Bool
> :: Pool -> Pool -> Bool
$c> :: Pool -> Pool -> Bool
<= :: Pool -> Pool -> Bool
$c<= :: Pool -> Pool -> Bool
< :: Pool -> Pool -> Bool
$c< :: Pool -> Pool -> Bool
compare :: Pool -> Pool -> Ordering
$ccompare :: Pool -> Pool -> Ordering
$cp1Ord :: Eq Pool
Ord, Ptr b -> Int -> IO Pool
Ptr b -> Int -> Pool -> IO ()
Ptr Pool -> IO Pool
Ptr Pool -> Int -> IO Pool
Ptr Pool -> Int -> Pool -> IO ()
Ptr Pool -> Pool -> IO ()
Pool -> Int
(Pool -> Int)
-> (Pool -> Int)
-> (Ptr Pool -> Int -> IO Pool)
-> (Ptr Pool -> Int -> Pool -> IO ())
-> (forall b. Ptr b -> Int -> IO Pool)
-> (forall b. Ptr b -> Int -> Pool -> IO ())
-> (Ptr Pool -> IO Pool)
-> (Ptr Pool -> Pool -> IO ())
-> Storable Pool
forall b. Ptr b -> Int -> IO Pool
forall b. Ptr b -> Int -> Pool -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Pool -> Pool -> IO ()
$cpoke :: Ptr Pool -> Pool -> IO ()
peek :: Ptr Pool -> IO Pool
$cpeek :: Ptr Pool -> IO Pool
pokeByteOff :: Ptr b -> Int -> Pool -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Pool -> IO ()
peekByteOff :: Ptr b -> Int -> IO Pool
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Pool
pokeElemOff :: Ptr Pool -> Int -> Pool -> IO ()
$cpokeElemOff :: Ptr Pool -> Int -> Pool -> IO ()
peekElemOff :: Ptr Pool -> Int -> IO Pool
$cpeekElemOff :: Ptr Pool -> Int -> IO Pool
alignment :: Pool -> Int
$calignment :: Pool -> Int
sizeOf :: Pool -> Int
$csizeOf :: Pool -> Int
Storable, Pool
Pool -> Zero Pool
forall a. a -> Zero a
zero :: Pool
$czero :: Pool
Zero)
deriving anyclass (Eq Pool
Zero Pool
(Eq Pool, Zero Pool) => IsHandle Pool
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Pool
$cp1IsHandle :: Eq Pool
IsHandle)
instance Show Pool where
showsPrec :: Int -> Pool -> ShowS
showsPrec p :: Int
p (Pool x :: "lostAllocationCount" ::: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Pool 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("lostAllocationCount" ::: Word64) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "lostAllocationCount" ::: Word64
x)
newtype MemoryUsage = MemoryUsage Int32
deriving newtype (MemoryUsage -> MemoryUsage -> Bool
(MemoryUsage -> MemoryUsage -> Bool)
-> (MemoryUsage -> MemoryUsage -> Bool) -> Eq MemoryUsage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MemoryUsage -> MemoryUsage -> Bool
$c/= :: MemoryUsage -> MemoryUsage -> Bool
== :: MemoryUsage -> MemoryUsage -> Bool
$c== :: MemoryUsage -> MemoryUsage -> Bool
Eq, Eq MemoryUsage
Eq MemoryUsage =>
(MemoryUsage -> MemoryUsage -> Ordering)
-> (MemoryUsage -> MemoryUsage -> Bool)
-> (MemoryUsage -> MemoryUsage -> Bool)
-> (MemoryUsage -> MemoryUsage -> Bool)
-> (MemoryUsage -> MemoryUsage -> Bool)
-> (MemoryUsage -> MemoryUsage -> MemoryUsage)
-> (MemoryUsage -> MemoryUsage -> MemoryUsage)
-> Ord MemoryUsage
MemoryUsage -> MemoryUsage -> Bool
MemoryUsage -> MemoryUsage -> Ordering
MemoryUsage -> MemoryUsage -> MemoryUsage
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: MemoryUsage -> MemoryUsage -> MemoryUsage
$cmin :: MemoryUsage -> MemoryUsage -> MemoryUsage
max :: MemoryUsage -> MemoryUsage -> MemoryUsage
$cmax :: MemoryUsage -> MemoryUsage -> MemoryUsage
>= :: MemoryUsage -> MemoryUsage -> Bool
$c>= :: MemoryUsage -> MemoryUsage -> Bool
> :: MemoryUsage -> MemoryUsage -> Bool
$c> :: MemoryUsage -> MemoryUsage -> Bool
<= :: MemoryUsage -> MemoryUsage -> Bool
$c<= :: MemoryUsage -> MemoryUsage -> Bool
< :: MemoryUsage -> MemoryUsage -> Bool
$c< :: MemoryUsage -> MemoryUsage -> Bool
compare :: MemoryUsage -> MemoryUsage -> Ordering
$ccompare :: MemoryUsage -> MemoryUsage -> Ordering
$cp1Ord :: Eq MemoryUsage
Ord, Ptr b -> Int -> IO MemoryUsage
Ptr b -> Int -> MemoryUsage -> IO ()
Ptr MemoryUsage -> IO MemoryUsage
Ptr MemoryUsage -> Int -> IO MemoryUsage
Ptr MemoryUsage -> Int -> MemoryUsage -> IO ()
Ptr MemoryUsage -> MemoryUsage -> IO ()
MemoryUsage -> Int
(MemoryUsage -> Int)
-> (MemoryUsage -> Int)
-> (Ptr MemoryUsage -> Int -> IO MemoryUsage)
-> (Ptr MemoryUsage -> Int -> MemoryUsage -> IO ())
-> (forall b. Ptr b -> Int -> IO MemoryUsage)
-> (forall b. Ptr b -> Int -> MemoryUsage -> IO ())
-> (Ptr MemoryUsage -> IO MemoryUsage)
-> (Ptr MemoryUsage -> MemoryUsage -> IO ())
-> Storable MemoryUsage
forall b. Ptr b -> Int -> IO MemoryUsage
forall b. Ptr b -> Int -> MemoryUsage -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr MemoryUsage -> MemoryUsage -> IO ()
$cpoke :: Ptr MemoryUsage -> MemoryUsage -> IO ()
peek :: Ptr MemoryUsage -> IO MemoryUsage
$cpeek :: Ptr MemoryUsage -> IO MemoryUsage
pokeByteOff :: Ptr b -> Int -> MemoryUsage -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> MemoryUsage -> IO ()
peekByteOff :: Ptr b -> Int -> IO MemoryUsage
$cpeekByteOff :: forall b. Ptr b -> Int -> IO MemoryUsage
pokeElemOff :: Ptr MemoryUsage -> Int -> MemoryUsage -> IO ()
$cpokeElemOff :: Ptr MemoryUsage -> Int -> MemoryUsage -> IO ()
peekElemOff :: Ptr MemoryUsage -> Int -> IO MemoryUsage
$cpeekElemOff :: Ptr MemoryUsage -> Int -> IO MemoryUsage
alignment :: MemoryUsage -> Int
$calignment :: MemoryUsage -> Int
sizeOf :: MemoryUsage -> Int
$csizeOf :: MemoryUsage -> Int
Storable, MemoryUsage
MemoryUsage -> Zero MemoryUsage
forall a. a -> Zero a
zero :: MemoryUsage
$czero :: MemoryUsage
Zero)
pattern $bMEMORY_USAGE_UNKNOWN :: MemoryUsage
$mMEMORY_USAGE_UNKNOWN :: forall r. MemoryUsage -> (Void# -> r) -> (Void# -> r) -> r
MEMORY_USAGE_UNKNOWN = MemoryUsage 0
pattern $bMEMORY_USAGE_GPU_ONLY :: MemoryUsage
$mMEMORY_USAGE_GPU_ONLY :: forall r. MemoryUsage -> (Void# -> r) -> (Void# -> r) -> r
MEMORY_USAGE_GPU_ONLY = MemoryUsage 1
pattern $bMEMORY_USAGE_CPU_ONLY :: MemoryUsage
$mMEMORY_USAGE_CPU_ONLY :: forall r. MemoryUsage -> (Void# -> r) -> (Void# -> r) -> r
MEMORY_USAGE_CPU_ONLY = MemoryUsage 2
pattern $bMEMORY_USAGE_CPU_TO_GPU :: MemoryUsage
$mMEMORY_USAGE_CPU_TO_GPU :: forall r. MemoryUsage -> (Void# -> r) -> (Void# -> r) -> r
MEMORY_USAGE_CPU_TO_GPU = MemoryUsage 3
pattern $bMEMORY_USAGE_GPU_TO_CPU :: MemoryUsage
$mMEMORY_USAGE_GPU_TO_CPU :: forall r. MemoryUsage -> (Void# -> r) -> (Void# -> r) -> r
MEMORY_USAGE_GPU_TO_CPU = MemoryUsage 4
pattern $bMEMORY_USAGE_CPU_COPY :: MemoryUsage
$mMEMORY_USAGE_CPU_COPY :: forall r. MemoryUsage -> (Void# -> r) -> (Void# -> r) -> r
MEMORY_USAGE_CPU_COPY = MemoryUsage 5
pattern $bMEMORY_USAGE_GPU_LAZILY_ALLOCATED :: MemoryUsage
$mMEMORY_USAGE_GPU_LAZILY_ALLOCATED :: forall r. MemoryUsage -> (Void# -> r) -> (Void# -> r) -> r
MEMORY_USAGE_GPU_LAZILY_ALLOCATED = MemoryUsage 6
{-# complete MEMORY_USAGE_UNKNOWN,
MEMORY_USAGE_GPU_ONLY,
MEMORY_USAGE_CPU_ONLY,
MEMORY_USAGE_CPU_TO_GPU,
MEMORY_USAGE_GPU_TO_CPU,
MEMORY_USAGE_CPU_COPY,
MEMORY_USAGE_GPU_LAZILY_ALLOCATED :: MemoryUsage #-}
instance Show MemoryUsage where
showsPrec :: Int -> MemoryUsage -> ShowS
showsPrec p :: Int
p = \case
MEMORY_USAGE_UNKNOWN -> String -> ShowS
showString "MEMORY_USAGE_UNKNOWN"
MEMORY_USAGE_GPU_ONLY -> String -> ShowS
showString "MEMORY_USAGE_GPU_ONLY"
MEMORY_USAGE_CPU_ONLY -> String -> ShowS
showString "MEMORY_USAGE_CPU_ONLY"
MEMORY_USAGE_CPU_TO_GPU -> String -> ShowS
showString "MEMORY_USAGE_CPU_TO_GPU"
MEMORY_USAGE_GPU_TO_CPU -> String -> ShowS
showString "MEMORY_USAGE_GPU_TO_CPU"
MEMORY_USAGE_CPU_COPY -> String -> ShowS
showString "MEMORY_USAGE_CPU_COPY"
MEMORY_USAGE_GPU_LAZILY_ALLOCATED -> String -> ShowS
showString "MEMORY_USAGE_GPU_LAZILY_ALLOCATED"
MemoryUsage x :: Int32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "MemoryUsage " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int32 -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec 11 Int32
x)
instance Read MemoryUsage where
readPrec :: ReadPrec MemoryUsage
readPrec = ReadPrec MemoryUsage -> ReadPrec MemoryUsage
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec MemoryUsage)] -> ReadPrec MemoryUsage
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("MEMORY_USAGE_UNKNOWN", MemoryUsage -> ReadPrec MemoryUsage
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryUsage
MEMORY_USAGE_UNKNOWN)
, ("MEMORY_USAGE_GPU_ONLY", MemoryUsage -> ReadPrec MemoryUsage
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryUsage
MEMORY_USAGE_GPU_ONLY)
, ("MEMORY_USAGE_CPU_ONLY", MemoryUsage -> ReadPrec MemoryUsage
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryUsage
MEMORY_USAGE_CPU_ONLY)
, ("MEMORY_USAGE_CPU_TO_GPU", MemoryUsage -> ReadPrec MemoryUsage
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryUsage
MEMORY_USAGE_CPU_TO_GPU)
, ("MEMORY_USAGE_GPU_TO_CPU", MemoryUsage -> ReadPrec MemoryUsage
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryUsage
MEMORY_USAGE_GPU_TO_CPU)
, ("MEMORY_USAGE_CPU_COPY", MemoryUsage -> ReadPrec MemoryUsage
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryUsage
MEMORY_USAGE_CPU_COPY)
, ("MEMORY_USAGE_GPU_LAZILY_ALLOCATED", MemoryUsage -> ReadPrec MemoryUsage
forall (f :: * -> *) a. Applicative f => a -> f a
pure MemoryUsage
MEMORY_USAGE_GPU_LAZILY_ALLOCATED)]
ReadPrec MemoryUsage
-> ReadPrec MemoryUsage -> ReadPrec MemoryUsage
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int -> ReadPrec MemoryUsage -> ReadPrec MemoryUsage
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "MemoryUsage")
Int32
v <- ReadPrec Int32 -> ReadPrec Int32
forall a. ReadPrec a -> ReadPrec a
step ReadPrec Int32
forall a. Read a => ReadPrec a
readPrec
MemoryUsage -> ReadPrec MemoryUsage
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Int32 -> MemoryUsage
MemoryUsage Int32
v)))
newtype AllocationCreateFlagBits = AllocationCreateFlagBits Flags
deriving newtype (AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
(AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool)
-> (AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool)
-> Eq AllocationCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
$c/= :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
== :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
$c== :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
Eq, Eq AllocationCreateFlagBits
Eq AllocationCreateFlagBits =>
(AllocationCreateFlagBits -> AllocationCreateFlagBits -> Ordering)
-> (AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool)
-> (AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool)
-> (AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool)
-> (AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool)
-> (AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits)
-> Ord AllocationCreateFlagBits
AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
AllocationCreateFlagBits -> AllocationCreateFlagBits -> Ordering
AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
$cmin :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
max :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
$cmax :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
>= :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
$c>= :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
> :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
$c> :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
<= :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
$c<= :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
< :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
$c< :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Bool
compare :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Ordering
$ccompare :: AllocationCreateFlagBits -> AllocationCreateFlagBits -> Ordering
$cp1Ord :: Eq AllocationCreateFlagBits
Ord, Ptr b -> Int -> IO AllocationCreateFlagBits
Ptr b -> Int -> AllocationCreateFlagBits -> IO ()
Ptr AllocationCreateFlagBits -> IO AllocationCreateFlagBits
Ptr AllocationCreateFlagBits -> Int -> IO AllocationCreateFlagBits
Ptr AllocationCreateFlagBits
-> Int -> AllocationCreateFlagBits -> IO ()
Ptr AllocationCreateFlagBits -> AllocationCreateFlagBits -> IO ()
AllocationCreateFlagBits -> Int
(AllocationCreateFlagBits -> Int)
-> (AllocationCreateFlagBits -> Int)
-> (Ptr AllocationCreateFlagBits
-> Int -> IO AllocationCreateFlagBits)
-> (Ptr AllocationCreateFlagBits
-> Int -> AllocationCreateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO AllocationCreateFlagBits)
-> (forall b. Ptr b -> Int -> AllocationCreateFlagBits -> IO ())
-> (Ptr AllocationCreateFlagBits -> IO AllocationCreateFlagBits)
-> (Ptr AllocationCreateFlagBits
-> AllocationCreateFlagBits -> IO ())
-> Storable AllocationCreateFlagBits
forall b. Ptr b -> Int -> IO AllocationCreateFlagBits
forall b. Ptr b -> Int -> AllocationCreateFlagBits -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr AllocationCreateFlagBits -> AllocationCreateFlagBits -> IO ()
$cpoke :: Ptr AllocationCreateFlagBits -> AllocationCreateFlagBits -> IO ()
peek :: Ptr AllocationCreateFlagBits -> IO AllocationCreateFlagBits
$cpeek :: Ptr AllocationCreateFlagBits -> IO AllocationCreateFlagBits
pokeByteOff :: Ptr b -> Int -> AllocationCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> AllocationCreateFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO AllocationCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO AllocationCreateFlagBits
pokeElemOff :: Ptr AllocationCreateFlagBits
-> Int -> AllocationCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr AllocationCreateFlagBits
-> Int -> AllocationCreateFlagBits -> IO ()
peekElemOff :: Ptr AllocationCreateFlagBits -> Int -> IO AllocationCreateFlagBits
$cpeekElemOff :: Ptr AllocationCreateFlagBits -> Int -> IO AllocationCreateFlagBits
alignment :: AllocationCreateFlagBits -> Int
$calignment :: AllocationCreateFlagBits -> Int
sizeOf :: AllocationCreateFlagBits -> Int
$csizeOf :: AllocationCreateFlagBits -> Int
Storable, AllocationCreateFlagBits
AllocationCreateFlagBits -> Zero AllocationCreateFlagBits
forall a. a -> Zero a
zero :: AllocationCreateFlagBits
$czero :: AllocationCreateFlagBits
Zero, Eq AllocationCreateFlagBits
AllocationCreateFlagBits
Eq AllocationCreateFlagBits =>
(AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> AllocationCreateFlagBits
-> (Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> Bool)
-> (AllocationCreateFlagBits -> Maybe Int)
-> (AllocationCreateFlagBits -> Int)
-> (AllocationCreateFlagBits -> Bool)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits)
-> (AllocationCreateFlagBits -> Int)
-> Bits AllocationCreateFlagBits
Int -> AllocationCreateFlagBits
AllocationCreateFlagBits -> Bool
AllocationCreateFlagBits -> Int
AllocationCreateFlagBits -> Maybe Int
AllocationCreateFlagBits -> AllocationCreateFlagBits
AllocationCreateFlagBits -> Int -> Bool
AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: AllocationCreateFlagBits -> Int
$cpopCount :: AllocationCreateFlagBits -> Int
rotateR :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$crotateR :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
rotateL :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$crotateL :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
unsafeShiftR :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$cunsafeShiftR :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
shiftR :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$cshiftR :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
unsafeShiftL :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$cunsafeShiftL :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
shiftL :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$cshiftL :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
isSigned :: AllocationCreateFlagBits -> Bool
$cisSigned :: AllocationCreateFlagBits -> Bool
bitSize :: AllocationCreateFlagBits -> Int
$cbitSize :: AllocationCreateFlagBits -> Int
bitSizeMaybe :: AllocationCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: AllocationCreateFlagBits -> Maybe Int
testBit :: AllocationCreateFlagBits -> Int -> Bool
$ctestBit :: AllocationCreateFlagBits -> Int -> Bool
complementBit :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$ccomplementBit :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
clearBit :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$cclearBit :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
setBit :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$csetBit :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
bit :: Int -> AllocationCreateFlagBits
$cbit :: Int -> AllocationCreateFlagBits
zeroBits :: AllocationCreateFlagBits
$czeroBits :: AllocationCreateFlagBits
rotate :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$crotate :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
shift :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
$cshift :: AllocationCreateFlagBits -> Int -> AllocationCreateFlagBits
complement :: AllocationCreateFlagBits -> AllocationCreateFlagBits
$ccomplement :: AllocationCreateFlagBits -> AllocationCreateFlagBits
xor :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
$cxor :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
.|. :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
$c.|. :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
.&. :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
$c.&. :: AllocationCreateFlagBits
-> AllocationCreateFlagBits -> AllocationCreateFlagBits
$cp1Bits :: Eq AllocationCreateFlagBits
Bits)
pattern $bALLOCATION_CREATE_DEDICATED_MEMORY_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_DEDICATED_MEMORY_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_DEDICATED_MEMORY_BIT = AllocationCreateFlagBits 0x00000001
pattern $bALLOCATION_CREATE_NEVER_ALLOCATE_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_NEVER_ALLOCATE_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_NEVER_ALLOCATE_BIT = AllocationCreateFlagBits 0x00000002
pattern $bALLOCATION_CREATE_MAPPED_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_MAPPED_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_MAPPED_BIT = AllocationCreateFlagBits 0x00000004
pattern $bALLOCATION_CREATE_CAN_BECOME_LOST_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_CAN_BECOME_LOST_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_CAN_BECOME_LOST_BIT = AllocationCreateFlagBits 0x00000008
pattern $bALLOCATION_CREATE_CAN_MAKE_OTHER_LOST_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_CAN_MAKE_OTHER_LOST_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_CAN_MAKE_OTHER_LOST_BIT = AllocationCreateFlagBits 0x00000010
pattern $bALLOCATION_CREATE_USER_DATA_COPY_STRING_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_USER_DATA_COPY_STRING_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_USER_DATA_COPY_STRING_BIT = AllocationCreateFlagBits 0x00000020
pattern $bALLOCATION_CREATE_UPPER_ADDRESS_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_UPPER_ADDRESS_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_UPPER_ADDRESS_BIT = AllocationCreateFlagBits 0x00000040
pattern $bALLOCATION_CREATE_DONT_BIND_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_DONT_BIND_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_DONT_BIND_BIT = AllocationCreateFlagBits 0x00000080
pattern $bALLOCATION_CREATE_WITHIN_BUDGET_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_WITHIN_BUDGET_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_WITHIN_BUDGET_BIT = AllocationCreateFlagBits 0x00000100
pattern $bALLOCATION_CREATE_STRATEGY_BEST_FIT_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_STRATEGY_BEST_FIT_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_STRATEGY_BEST_FIT_BIT = AllocationCreateFlagBits 0x00010000
pattern $bALLOCATION_CREATE_STRATEGY_WORST_FIT_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_STRATEGY_WORST_FIT_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_STRATEGY_WORST_FIT_BIT = AllocationCreateFlagBits 0x00020000
pattern $bALLOCATION_CREATE_STRATEGY_FIRST_FIT_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_STRATEGY_FIRST_FIT_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_STRATEGY_FIRST_FIT_BIT = AllocationCreateFlagBits 0x00040000
pattern $bALLOCATION_CREATE_STRATEGY_MIN_MEMORY_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_STRATEGY_MIN_MEMORY_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_STRATEGY_MIN_MEMORY_BIT = AllocationCreateFlagBits 0x00010000
pattern $bALLOCATION_CREATE_STRATEGY_MIN_TIME_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_STRATEGY_MIN_TIME_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_STRATEGY_MIN_TIME_BIT = AllocationCreateFlagBits 0x00040000
pattern $bALLOCATION_CREATE_STRATEGY_MIN_FRAGMENTATION_BIT :: AllocationCreateFlagBits
$mALLOCATION_CREATE_STRATEGY_MIN_FRAGMENTATION_BIT :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_STRATEGY_MIN_FRAGMENTATION_BIT = AllocationCreateFlagBits 0x00020000
pattern $bALLOCATION_CREATE_STRATEGY_MASK :: AllocationCreateFlagBits
$mALLOCATION_CREATE_STRATEGY_MASK :: forall r.
AllocationCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
ALLOCATION_CREATE_STRATEGY_MASK = AllocationCreateFlagBits 0x00070000
type AllocationCreateFlags = AllocationCreateFlagBits
instance Show AllocationCreateFlagBits where
showsPrec :: Int -> AllocationCreateFlagBits -> ShowS
showsPrec p :: Int
p = \case
ALLOCATION_CREATE_DEDICATED_MEMORY_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_DEDICATED_MEMORY_BIT"
ALLOCATION_CREATE_NEVER_ALLOCATE_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_NEVER_ALLOCATE_BIT"
ALLOCATION_CREATE_MAPPED_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_MAPPED_BIT"
ALLOCATION_CREATE_CAN_BECOME_LOST_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_CAN_BECOME_LOST_BIT"
ALLOCATION_CREATE_CAN_MAKE_OTHER_LOST_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_CAN_MAKE_OTHER_LOST_BIT"
ALLOCATION_CREATE_USER_DATA_COPY_STRING_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_USER_DATA_COPY_STRING_BIT"
ALLOCATION_CREATE_UPPER_ADDRESS_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_UPPER_ADDRESS_BIT"
ALLOCATION_CREATE_DONT_BIND_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_DONT_BIND_BIT"
ALLOCATION_CREATE_WITHIN_BUDGET_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_WITHIN_BUDGET_BIT"
ALLOCATION_CREATE_STRATEGY_BEST_FIT_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_STRATEGY_BEST_FIT_BIT"
ALLOCATION_CREATE_STRATEGY_WORST_FIT_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_STRATEGY_WORST_FIT_BIT"
ALLOCATION_CREATE_STRATEGY_FIRST_FIT_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_STRATEGY_FIRST_FIT_BIT"
ALLOCATION_CREATE_STRATEGY_MIN_MEMORY_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_STRATEGY_MIN_MEMORY_BIT"
ALLOCATION_CREATE_STRATEGY_MIN_TIME_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_STRATEGY_MIN_TIME_BIT"
ALLOCATION_CREATE_STRATEGY_MIN_FRAGMENTATION_BIT -> String -> ShowS
showString "ALLOCATION_CREATE_STRATEGY_MIN_FRAGMENTATION_BIT"
ALLOCATION_CREATE_STRATEGY_MASK -> String -> ShowS
showString "ALLOCATION_CREATE_STRATEGY_MASK"
AllocationCreateFlagBits x :: "memoryTypeIndex" ::: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "AllocationCreateFlagBits 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("memoryTypeIndex" ::: Word32) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "memoryTypeIndex" ::: Word32
x)
instance Read AllocationCreateFlagBits where
readPrec :: ReadPrec AllocationCreateFlagBits
readPrec = ReadPrec AllocationCreateFlagBits
-> ReadPrec AllocationCreateFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec AllocationCreateFlagBits)]
-> ReadPrec AllocationCreateFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("ALLOCATION_CREATE_DEDICATED_MEMORY_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_DEDICATED_MEMORY_BIT)
, ("ALLOCATION_CREATE_NEVER_ALLOCATE_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_NEVER_ALLOCATE_BIT)
, ("ALLOCATION_CREATE_MAPPED_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_MAPPED_BIT)
, ("ALLOCATION_CREATE_CAN_BECOME_LOST_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_CAN_BECOME_LOST_BIT)
, ("ALLOCATION_CREATE_CAN_MAKE_OTHER_LOST_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_CAN_MAKE_OTHER_LOST_BIT)
, ("ALLOCATION_CREATE_USER_DATA_COPY_STRING_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_USER_DATA_COPY_STRING_BIT)
, ("ALLOCATION_CREATE_UPPER_ADDRESS_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_UPPER_ADDRESS_BIT)
, ("ALLOCATION_CREATE_DONT_BIND_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_DONT_BIND_BIT)
, ("ALLOCATION_CREATE_WITHIN_BUDGET_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_WITHIN_BUDGET_BIT)
, ("ALLOCATION_CREATE_STRATEGY_BEST_FIT_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_STRATEGY_BEST_FIT_BIT)
, ("ALLOCATION_CREATE_STRATEGY_WORST_FIT_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_STRATEGY_WORST_FIT_BIT)
, ("ALLOCATION_CREATE_STRATEGY_FIRST_FIT_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_STRATEGY_FIRST_FIT_BIT)
, ("ALLOCATION_CREATE_STRATEGY_MIN_MEMORY_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_STRATEGY_MIN_MEMORY_BIT)
, ("ALLOCATION_CREATE_STRATEGY_MIN_TIME_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_STRATEGY_MIN_TIME_BIT)
, ("ALLOCATION_CREATE_STRATEGY_MIN_FRAGMENTATION_BIT", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_STRATEGY_MIN_FRAGMENTATION_BIT)
, ("ALLOCATION_CREATE_STRATEGY_MASK", AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure AllocationCreateFlagBits
ALLOCATION_CREATE_STRATEGY_MASK)]
ReadPrec AllocationCreateFlagBits
-> ReadPrec AllocationCreateFlagBits
-> ReadPrec AllocationCreateFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec AllocationCreateFlagBits
-> ReadPrec AllocationCreateFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "AllocationCreateFlagBits")
"memoryTypeIndex" ::: Word32
v <- ReadPrec ("memoryTypeIndex" ::: Word32)
-> ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. Read a => ReadPrec a
readPrec
AllocationCreateFlagBits -> ReadPrec AllocationCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("memoryTypeIndex" ::: Word32) -> AllocationCreateFlagBits
AllocationCreateFlagBits "memoryTypeIndex" ::: Word32
v)))
data AllocationCreateInfo = AllocationCreateInfo
{
AllocationCreateInfo -> AllocationCreateFlagBits
flags :: AllocationCreateFlags
,
AllocationCreateInfo -> MemoryUsage
usage :: MemoryUsage
,
AllocationCreateInfo -> MemoryPropertyFlags
requiredFlags :: MemoryPropertyFlags
,
AllocationCreateInfo -> MemoryPropertyFlags
preferredFlags :: MemoryPropertyFlags
,
AllocationCreateInfo -> "memoryTypeIndex" ::: Word32
memoryTypeBits :: Word32
,
AllocationCreateInfo -> Pool
pool :: Pool
,
AllocationCreateInfo -> "userData" ::: Ptr ()
userData :: Ptr ()
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AllocationCreateInfo)
#endif
deriving instance Show AllocationCreateInfo
instance ToCStruct AllocationCreateInfo where
withCStruct :: AllocationCreateInfo -> (Ptr AllocationCreateInfo -> IO b) -> IO b
withCStruct x :: AllocationCreateInfo
x f :: Ptr AllocationCreateInfo -> IO b
f = Int -> Int -> (Ptr AllocationCreateInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr AllocationCreateInfo -> IO b) -> IO b)
-> (Ptr AllocationCreateInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AllocationCreateInfo
p -> Ptr AllocationCreateInfo -> AllocationCreateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AllocationCreateInfo
p AllocationCreateInfo
x (Ptr AllocationCreateInfo -> IO b
f Ptr AllocationCreateInfo
p)
pokeCStruct :: Ptr AllocationCreateInfo -> AllocationCreateInfo -> IO b -> IO b
pokeCStruct p :: Ptr AllocationCreateInfo
p AllocationCreateInfo{..} f :: IO b
f = do
Ptr AllocationCreateFlagBits -> AllocationCreateFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr AllocationCreateFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr AllocationCreateFlags)) (AllocationCreateFlagBits
flags)
Ptr MemoryUsage -> MemoryUsage -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr MemoryUsage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr MemoryUsage)) (MemoryUsage
usage)
Ptr MemoryPropertyFlags -> MemoryPropertyFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr MemoryPropertyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr MemoryPropertyFlags)) (MemoryPropertyFlags
requiredFlags)
Ptr MemoryPropertyFlags -> MemoryPropertyFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr MemoryPropertyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr MemoryPropertyFlags)) (MemoryPropertyFlags
preferredFlags)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
memoryTypeBits)
Ptr Pool -> Pool -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr Pool
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Pool)) (Pool
pool)
Ptr ("userData" ::: Ptr ()) -> ("userData" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr ("userData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr ()))) ("userData" ::: Ptr ()
userData)
IO b
f
cStructSize :: Int
cStructSize = 40
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr AllocationCreateInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr AllocationCreateInfo
p f :: IO b
f = do
Ptr AllocationCreateFlagBits -> AllocationCreateFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr AllocationCreateFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr AllocationCreateFlags)) (AllocationCreateFlagBits
forall a. Zero a => a
zero)
Ptr MemoryUsage -> MemoryUsage -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr MemoryUsage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr MemoryUsage)) (MemoryUsage
forall a. Zero a => a
zero)
Ptr MemoryPropertyFlags -> MemoryPropertyFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr MemoryPropertyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr MemoryPropertyFlags)) (MemoryPropertyFlags
forall a. Zero a => a
zero)
Ptr MemoryPropertyFlags -> MemoryPropertyFlags -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr MemoryPropertyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr MemoryPropertyFlags)) (MemoryPropertyFlags
forall a. Zero a => a
zero)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct AllocationCreateInfo where
peekCStruct :: Ptr AllocationCreateInfo -> IO AllocationCreateInfo
peekCStruct p :: Ptr AllocationCreateInfo
p = do
AllocationCreateFlagBits
flags <- Ptr AllocationCreateFlagBits -> IO AllocationCreateFlagBits
forall a. Storable a => Ptr a -> IO a
peek @AllocationCreateFlags ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr AllocationCreateFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr AllocationCreateFlags))
MemoryUsage
usage <- Ptr MemoryUsage -> IO MemoryUsage
forall a. Storable a => Ptr a -> IO a
peek @MemoryUsage ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr MemoryUsage
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr MemoryUsage))
MemoryPropertyFlags
requiredFlags <- Ptr MemoryPropertyFlags -> IO MemoryPropertyFlags
forall a. Storable a => Ptr a -> IO a
peek @MemoryPropertyFlags ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr MemoryPropertyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr MemoryPropertyFlags))
MemoryPropertyFlags
preferredFlags <- Ptr MemoryPropertyFlags -> IO MemoryPropertyFlags
forall a. Storable a => Ptr a -> IO a
peek @MemoryPropertyFlags ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr MemoryPropertyFlags
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12 :: Ptr MemoryPropertyFlags))
"memoryTypeIndex" ::: Word32
memoryTypeBits <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
Pool
pool <- Ptr Pool -> IO Pool
forall a. Storable a => Ptr a -> IO a
peek @Pool ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr Pool
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Pool))
"userData" ::: Ptr ()
pUserData <- Ptr ("userData" ::: Ptr ()) -> IO ("userData" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr AllocationCreateInfo
p Ptr AllocationCreateInfo -> Int -> Ptr ("userData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr ())))
AllocationCreateInfo -> IO AllocationCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AllocationCreateInfo -> IO AllocationCreateInfo)
-> AllocationCreateInfo -> IO AllocationCreateInfo
forall a b. (a -> b) -> a -> b
$ AllocationCreateFlagBits
-> MemoryUsage
-> MemoryPropertyFlags
-> MemoryPropertyFlags
-> ("memoryTypeIndex" ::: Word32)
-> Pool
-> ("userData" ::: Ptr ())
-> AllocationCreateInfo
AllocationCreateInfo
AllocationCreateFlagBits
flags MemoryUsage
usage MemoryPropertyFlags
requiredFlags MemoryPropertyFlags
preferredFlags "memoryTypeIndex" ::: Word32
memoryTypeBits Pool
pool "userData" ::: Ptr ()
pUserData
instance Storable AllocationCreateInfo where
sizeOf :: AllocationCreateInfo -> Int
sizeOf ~AllocationCreateInfo
_ = 40
alignment :: AllocationCreateInfo -> Int
alignment ~AllocationCreateInfo
_ = 8
peek :: Ptr AllocationCreateInfo -> IO AllocationCreateInfo
peek = Ptr AllocationCreateInfo -> IO AllocationCreateInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr AllocationCreateInfo -> AllocationCreateInfo -> IO ()
poke ptr :: Ptr AllocationCreateInfo
ptr poked :: AllocationCreateInfo
poked = Ptr AllocationCreateInfo -> AllocationCreateInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AllocationCreateInfo
ptr AllocationCreateInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero AllocationCreateInfo where
zero :: AllocationCreateInfo
zero = AllocationCreateFlagBits
-> MemoryUsage
-> MemoryPropertyFlags
-> MemoryPropertyFlags
-> ("memoryTypeIndex" ::: Word32)
-> Pool
-> ("userData" ::: Ptr ())
-> AllocationCreateInfo
AllocationCreateInfo
AllocationCreateFlagBits
forall a. Zero a => a
zero
MemoryUsage
forall a. Zero a => a
zero
MemoryPropertyFlags
forall a. Zero a => a
zero
MemoryPropertyFlags
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
Pool
forall a. Zero a => a
zero
"userData" ::: Ptr ()
forall a. Zero a => a
zero
newtype PoolCreateFlagBits = PoolCreateFlagBits Flags
deriving newtype (PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
(PoolCreateFlagBits -> PoolCreateFlagBits -> Bool)
-> (PoolCreateFlagBits -> PoolCreateFlagBits -> Bool)
-> Eq PoolCreateFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
$c/= :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
== :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
$c== :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
Eq, Eq PoolCreateFlagBits
Eq PoolCreateFlagBits =>
(PoolCreateFlagBits -> PoolCreateFlagBits -> Ordering)
-> (PoolCreateFlagBits -> PoolCreateFlagBits -> Bool)
-> (PoolCreateFlagBits -> PoolCreateFlagBits -> Bool)
-> (PoolCreateFlagBits -> PoolCreateFlagBits -> Bool)
-> (PoolCreateFlagBits -> PoolCreateFlagBits -> Bool)
-> (PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits)
-> Ord PoolCreateFlagBits
PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
PoolCreateFlagBits -> PoolCreateFlagBits -> Ordering
PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
$cmin :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
max :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
$cmax :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
>= :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
$c>= :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
> :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
$c> :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
<= :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
$c<= :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
< :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
$c< :: PoolCreateFlagBits -> PoolCreateFlagBits -> Bool
compare :: PoolCreateFlagBits -> PoolCreateFlagBits -> Ordering
$ccompare :: PoolCreateFlagBits -> PoolCreateFlagBits -> Ordering
$cp1Ord :: Eq PoolCreateFlagBits
Ord, Ptr b -> Int -> IO PoolCreateFlagBits
Ptr b -> Int -> PoolCreateFlagBits -> IO ()
Ptr PoolCreateFlagBits -> IO PoolCreateFlagBits
Ptr PoolCreateFlagBits -> Int -> IO PoolCreateFlagBits
Ptr PoolCreateFlagBits -> Int -> PoolCreateFlagBits -> IO ()
Ptr PoolCreateFlagBits -> PoolCreateFlagBits -> IO ()
PoolCreateFlagBits -> Int
(PoolCreateFlagBits -> Int)
-> (PoolCreateFlagBits -> Int)
-> (Ptr PoolCreateFlagBits -> Int -> IO PoolCreateFlagBits)
-> (Ptr PoolCreateFlagBits -> Int -> PoolCreateFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO PoolCreateFlagBits)
-> (forall b. Ptr b -> Int -> PoolCreateFlagBits -> IO ())
-> (Ptr PoolCreateFlagBits -> IO PoolCreateFlagBits)
-> (Ptr PoolCreateFlagBits -> PoolCreateFlagBits -> IO ())
-> Storable PoolCreateFlagBits
forall b. Ptr b -> Int -> IO PoolCreateFlagBits
forall b. Ptr b -> Int -> PoolCreateFlagBits -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr PoolCreateFlagBits -> PoolCreateFlagBits -> IO ()
$cpoke :: Ptr PoolCreateFlagBits -> PoolCreateFlagBits -> IO ()
peek :: Ptr PoolCreateFlagBits -> IO PoolCreateFlagBits
$cpeek :: Ptr PoolCreateFlagBits -> IO PoolCreateFlagBits
pokeByteOff :: Ptr b -> Int -> PoolCreateFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> PoolCreateFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO PoolCreateFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO PoolCreateFlagBits
pokeElemOff :: Ptr PoolCreateFlagBits -> Int -> PoolCreateFlagBits -> IO ()
$cpokeElemOff :: Ptr PoolCreateFlagBits -> Int -> PoolCreateFlagBits -> IO ()
peekElemOff :: Ptr PoolCreateFlagBits -> Int -> IO PoolCreateFlagBits
$cpeekElemOff :: Ptr PoolCreateFlagBits -> Int -> IO PoolCreateFlagBits
alignment :: PoolCreateFlagBits -> Int
$calignment :: PoolCreateFlagBits -> Int
sizeOf :: PoolCreateFlagBits -> Int
$csizeOf :: PoolCreateFlagBits -> Int
Storable, PoolCreateFlagBits
PoolCreateFlagBits -> Zero PoolCreateFlagBits
forall a. a -> Zero a
zero :: PoolCreateFlagBits
$czero :: PoolCreateFlagBits
Zero, Eq PoolCreateFlagBits
PoolCreateFlagBits
Eq PoolCreateFlagBits =>
(PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> PoolCreateFlagBits
-> (Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> Bool)
-> (PoolCreateFlagBits -> Maybe Int)
-> (PoolCreateFlagBits -> Int)
-> (PoolCreateFlagBits -> Bool)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int -> PoolCreateFlagBits)
-> (PoolCreateFlagBits -> Int)
-> Bits PoolCreateFlagBits
Int -> PoolCreateFlagBits
PoolCreateFlagBits -> Bool
PoolCreateFlagBits -> Int
PoolCreateFlagBits -> Maybe Int
PoolCreateFlagBits -> PoolCreateFlagBits
PoolCreateFlagBits -> Int -> Bool
PoolCreateFlagBits -> Int -> PoolCreateFlagBits
PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: PoolCreateFlagBits -> Int
$cpopCount :: PoolCreateFlagBits -> Int
rotateR :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$crotateR :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
rotateL :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$crotateL :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
unsafeShiftR :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$cunsafeShiftR :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
shiftR :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$cshiftR :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
unsafeShiftL :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$cunsafeShiftL :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
shiftL :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$cshiftL :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
isSigned :: PoolCreateFlagBits -> Bool
$cisSigned :: PoolCreateFlagBits -> Bool
bitSize :: PoolCreateFlagBits -> Int
$cbitSize :: PoolCreateFlagBits -> Int
bitSizeMaybe :: PoolCreateFlagBits -> Maybe Int
$cbitSizeMaybe :: PoolCreateFlagBits -> Maybe Int
testBit :: PoolCreateFlagBits -> Int -> Bool
$ctestBit :: PoolCreateFlagBits -> Int -> Bool
complementBit :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$ccomplementBit :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
clearBit :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$cclearBit :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
setBit :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$csetBit :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
bit :: Int -> PoolCreateFlagBits
$cbit :: Int -> PoolCreateFlagBits
zeroBits :: PoolCreateFlagBits
$czeroBits :: PoolCreateFlagBits
rotate :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$crotate :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
shift :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
$cshift :: PoolCreateFlagBits -> Int -> PoolCreateFlagBits
complement :: PoolCreateFlagBits -> PoolCreateFlagBits
$ccomplement :: PoolCreateFlagBits -> PoolCreateFlagBits
xor :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
$cxor :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
.|. :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
$c.|. :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
.&. :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
$c.&. :: PoolCreateFlagBits -> PoolCreateFlagBits -> PoolCreateFlagBits
$cp1Bits :: Eq PoolCreateFlagBits
Bits)
pattern $bPOOL_CREATE_IGNORE_BUFFER_IMAGE_GRANULARITY_BIT :: PoolCreateFlagBits
$mPOOL_CREATE_IGNORE_BUFFER_IMAGE_GRANULARITY_BIT :: forall r. PoolCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
POOL_CREATE_IGNORE_BUFFER_IMAGE_GRANULARITY_BIT = PoolCreateFlagBits 0x00000002
pattern $bPOOL_CREATE_LINEAR_ALGORITHM_BIT :: PoolCreateFlagBits
$mPOOL_CREATE_LINEAR_ALGORITHM_BIT :: forall r. PoolCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
POOL_CREATE_LINEAR_ALGORITHM_BIT = PoolCreateFlagBits 0x00000004
pattern $bPOOL_CREATE_BUDDY_ALGORITHM_BIT :: PoolCreateFlagBits
$mPOOL_CREATE_BUDDY_ALGORITHM_BIT :: forall r. PoolCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
POOL_CREATE_BUDDY_ALGORITHM_BIT = PoolCreateFlagBits 0x00000008
pattern $bPOOL_CREATE_ALGORITHM_MASK :: PoolCreateFlagBits
$mPOOL_CREATE_ALGORITHM_MASK :: forall r. PoolCreateFlagBits -> (Void# -> r) -> (Void# -> r) -> r
POOL_CREATE_ALGORITHM_MASK = PoolCreateFlagBits 0x0000000c
type PoolCreateFlags = PoolCreateFlagBits
instance Show PoolCreateFlagBits where
showsPrec :: Int -> PoolCreateFlagBits -> ShowS
showsPrec p :: Int
p = \case
POOL_CREATE_IGNORE_BUFFER_IMAGE_GRANULARITY_BIT -> String -> ShowS
showString "POOL_CREATE_IGNORE_BUFFER_IMAGE_GRANULARITY_BIT"
POOL_CREATE_LINEAR_ALGORITHM_BIT -> String -> ShowS
showString "POOL_CREATE_LINEAR_ALGORITHM_BIT"
POOL_CREATE_BUDDY_ALGORITHM_BIT -> String -> ShowS
showString "POOL_CREATE_BUDDY_ALGORITHM_BIT"
POOL_CREATE_ALGORITHM_MASK -> String -> ShowS
showString "POOL_CREATE_ALGORITHM_MASK"
PoolCreateFlagBits x :: "memoryTypeIndex" ::: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "PoolCreateFlagBits 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("memoryTypeIndex" ::: Word32) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "memoryTypeIndex" ::: Word32
x)
instance Read PoolCreateFlagBits where
readPrec :: ReadPrec PoolCreateFlagBits
readPrec = ReadPrec PoolCreateFlagBits -> ReadPrec PoolCreateFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec PoolCreateFlagBits)]
-> ReadPrec PoolCreateFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("POOL_CREATE_IGNORE_BUFFER_IMAGE_GRANULARITY_BIT", PoolCreateFlagBits -> ReadPrec PoolCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PoolCreateFlagBits
POOL_CREATE_IGNORE_BUFFER_IMAGE_GRANULARITY_BIT)
, ("POOL_CREATE_LINEAR_ALGORITHM_BIT", PoolCreateFlagBits -> ReadPrec PoolCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PoolCreateFlagBits
POOL_CREATE_LINEAR_ALGORITHM_BIT)
, ("POOL_CREATE_BUDDY_ALGORITHM_BIT", PoolCreateFlagBits -> ReadPrec PoolCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PoolCreateFlagBits
POOL_CREATE_BUDDY_ALGORITHM_BIT)
, ("POOL_CREATE_ALGORITHM_MASK", PoolCreateFlagBits -> ReadPrec PoolCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure PoolCreateFlagBits
POOL_CREATE_ALGORITHM_MASK)]
ReadPrec PoolCreateFlagBits
-> ReadPrec PoolCreateFlagBits -> ReadPrec PoolCreateFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int -> ReadPrec PoolCreateFlagBits -> ReadPrec PoolCreateFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "PoolCreateFlagBits")
"memoryTypeIndex" ::: Word32
v <- ReadPrec ("memoryTypeIndex" ::: Word32)
-> ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. Read a => ReadPrec a
readPrec
PoolCreateFlagBits -> ReadPrec PoolCreateFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("memoryTypeIndex" ::: Word32) -> PoolCreateFlagBits
PoolCreateFlagBits "memoryTypeIndex" ::: Word32
v)))
data PoolCreateInfo = PoolCreateInfo
{
PoolCreateInfo -> "memoryTypeIndex" ::: Word32
memoryTypeIndex :: Word32
,
PoolCreateInfo -> PoolCreateFlagBits
flags :: PoolCreateFlags
,
PoolCreateInfo -> "lostAllocationCount" ::: Word64
blockSize :: DeviceSize
,
PoolCreateInfo -> "lostAllocationCount" ::: Word64
minBlockCount :: Word64
,
PoolCreateInfo -> "lostAllocationCount" ::: Word64
maxBlockCount :: Word64
,
PoolCreateInfo -> "memoryTypeIndex" ::: Word32
frameInUseCount :: Word32
}
deriving (Typeable, PoolCreateInfo -> PoolCreateInfo -> Bool
(PoolCreateInfo -> PoolCreateInfo -> Bool)
-> (PoolCreateInfo -> PoolCreateInfo -> Bool) -> Eq PoolCreateInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolCreateInfo -> PoolCreateInfo -> Bool
$c/= :: PoolCreateInfo -> PoolCreateInfo -> Bool
== :: PoolCreateInfo -> PoolCreateInfo -> Bool
$c== :: PoolCreateInfo -> PoolCreateInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PoolCreateInfo)
#endif
deriving instance Show PoolCreateInfo
instance ToCStruct PoolCreateInfo where
withCStruct :: PoolCreateInfo -> (Ptr PoolCreateInfo -> IO b) -> IO b
withCStruct x :: PoolCreateInfo
x f :: Ptr PoolCreateInfo -> IO b
f = Int -> Int -> (Ptr PoolCreateInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 40 8 ((Ptr PoolCreateInfo -> IO b) -> IO b)
-> (Ptr PoolCreateInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PoolCreateInfo
p -> Ptr PoolCreateInfo -> PoolCreateInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PoolCreateInfo
p PoolCreateInfo
x (Ptr PoolCreateInfo -> IO b
f Ptr PoolCreateInfo
p)
pokeCStruct :: Ptr PoolCreateInfo -> PoolCreateInfo -> IO b -> IO b
pokeCStruct p :: Ptr PoolCreateInfo
p PoolCreateInfo{..} f :: IO b
f = do
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
memoryTypeIndex)
Ptr PoolCreateFlagBits -> PoolCreateFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr PoolCreateFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr PoolCreateFlags)) (PoolCreateFlagBits
flags)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
blockSize)
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
minBlockCount))
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
maxBlockCount))
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
frameInUseCount)
IO b
f
cStructSize :: Int
cStructSize = 40
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PoolCreateInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr PoolCreateInfo
p f :: IO b
f = do
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
Ptr PoolCreateFlagBits -> PoolCreateFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr PoolCreateFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr PoolCreateFlags)) (PoolCreateFlagBits
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero))
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero))
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct PoolCreateInfo where
peekCStruct :: Ptr PoolCreateInfo -> IO PoolCreateInfo
peekCStruct p :: Ptr PoolCreateInfo
p = do
"memoryTypeIndex" ::: Word32
memoryTypeIndex <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
PoolCreateFlagBits
flags <- Ptr PoolCreateFlagBits -> IO PoolCreateFlagBits
forall a. Storable a => Ptr a -> IO a
peek @PoolCreateFlags ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr PoolCreateFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr PoolCreateFlags))
"lostAllocationCount" ::: Word64
blockSize <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize))
CSize
minBlockCount <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CSize))
CSize
maxBlockCount <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr CSize))
"memoryTypeIndex" ::: Word32
frameInUseCount <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr PoolCreateInfo
p Ptr PoolCreateInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr Word32))
PoolCreateInfo -> IO PoolCreateInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PoolCreateInfo -> IO PoolCreateInfo)
-> PoolCreateInfo -> IO PoolCreateInfo
forall a b. (a -> b) -> a -> b
$ ("memoryTypeIndex" ::: Word32)
-> PoolCreateFlagBits
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32)
-> PoolCreateInfo
PoolCreateInfo
"memoryTypeIndex" ::: Word32
memoryTypeIndex PoolCreateFlagBits
flags "lostAllocationCount" ::: Word64
blockSize ((\(CSize a :: "lostAllocationCount" ::: Word64
a) -> "lostAllocationCount" ::: Word64
a) CSize
minBlockCount) ((\(CSize a :: "lostAllocationCount" ::: Word64
a) -> "lostAllocationCount" ::: Word64
a) CSize
maxBlockCount) "memoryTypeIndex" ::: Word32
frameInUseCount
instance Storable PoolCreateInfo where
sizeOf :: PoolCreateInfo -> Int
sizeOf ~PoolCreateInfo
_ = 40
alignment :: PoolCreateInfo -> Int
alignment ~PoolCreateInfo
_ = 8
peek :: Ptr PoolCreateInfo -> IO PoolCreateInfo
peek = Ptr PoolCreateInfo -> IO PoolCreateInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PoolCreateInfo -> PoolCreateInfo -> IO ()
poke ptr :: Ptr PoolCreateInfo
ptr poked :: PoolCreateInfo
poked = Ptr PoolCreateInfo -> PoolCreateInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PoolCreateInfo
ptr PoolCreateInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PoolCreateInfo where
zero :: PoolCreateInfo
zero = ("memoryTypeIndex" ::: Word32)
-> PoolCreateFlagBits
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32)
-> PoolCreateInfo
PoolCreateInfo
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
PoolCreateFlagBits
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
data PoolStats = PoolStats
{
PoolStats -> "lostAllocationCount" ::: Word64
size :: DeviceSize
,
PoolStats -> "lostAllocationCount" ::: Word64
unusedSize :: DeviceSize
,
PoolStats -> "lostAllocationCount" ::: Word64
allocationCount :: Word64
,
PoolStats -> "lostAllocationCount" ::: Word64
unusedRangeCount :: Word64
,
PoolStats -> "lostAllocationCount" ::: Word64
unusedRangeSizeMax :: DeviceSize
,
PoolStats -> "lostAllocationCount" ::: Word64
blockCount :: Word64
}
deriving (Typeable, PoolStats -> PoolStats -> Bool
(PoolStats -> PoolStats -> Bool)
-> (PoolStats -> PoolStats -> Bool) -> Eq PoolStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PoolStats -> PoolStats -> Bool
$c/= :: PoolStats -> PoolStats -> Bool
== :: PoolStats -> PoolStats -> Bool
$c== :: PoolStats -> PoolStats -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (PoolStats)
#endif
deriving instance Show PoolStats
instance ToCStruct PoolStats where
withCStruct :: PoolStats -> (Ptr PoolStats -> IO b) -> IO b
withCStruct x :: PoolStats
x f :: Ptr PoolStats -> IO b
f = Int -> Int -> (Ptr PoolStats -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr PoolStats -> IO b) -> IO b)
-> (Ptr PoolStats -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr PoolStats
p -> Ptr PoolStats -> PoolStats -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PoolStats
p PoolStats
x (Ptr PoolStats -> IO b
f Ptr PoolStats
p)
pokeCStruct :: Ptr PoolStats -> PoolStats -> IO b -> IO b
pokeCStruct p :: Ptr PoolStats
p PoolStats{..} f :: IO b
f = do
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
size)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
unusedSize)
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
allocationCount))
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
unusedRangeCount))
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
unusedRangeSizeMax)
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
blockCount))
IO b
f
cStructSize :: Int
cStructSize = 48
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr PoolStats -> IO b -> IO b
pokeZeroCStruct p :: Ptr PoolStats
p f :: IO b
f = do
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero))
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero))
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr CSize -> CSize -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr CSize)) (("lostAllocationCount" ::: Word64) -> CSize
CSize ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero))
IO b
f
instance FromCStruct PoolStats where
peekCStruct :: Ptr PoolStats -> IO PoolStats
peekCStruct p :: Ptr PoolStats
p = do
"lostAllocationCount" ::: Word64
size <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
unusedSize <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize))
CSize
allocationCount <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr CSize))
CSize
unusedRangeCount <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr CSize))
"lostAllocationCount" ::: Word64
unusedRangeSizeMax <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr DeviceSize))
CSize
blockCount <- Ptr CSize -> IO CSize
forall a. Storable a => Ptr a -> IO a
peek @CSize ((Ptr PoolStats
p Ptr PoolStats -> Int -> Ptr CSize
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr CSize))
PoolStats -> IO PoolStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PoolStats -> IO PoolStats) -> PoolStats -> IO PoolStats
forall a b. (a -> b) -> a -> b
$ ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> PoolStats
PoolStats
"lostAllocationCount" ::: Word64
size "lostAllocationCount" ::: Word64
unusedSize ((\(CSize a :: "lostAllocationCount" ::: Word64
a) -> "lostAllocationCount" ::: Word64
a) CSize
allocationCount) ((\(CSize a :: "lostAllocationCount" ::: Word64
a) -> "lostAllocationCount" ::: Word64
a) CSize
unusedRangeCount) "lostAllocationCount" ::: Word64
unusedRangeSizeMax ((\(CSize a :: "lostAllocationCount" ::: Word64
a) -> "lostAllocationCount" ::: Word64
a) CSize
blockCount)
instance Storable PoolStats where
sizeOf :: PoolStats -> Int
sizeOf ~PoolStats
_ = 48
alignment :: PoolStats -> Int
alignment ~PoolStats
_ = 8
peek :: Ptr PoolStats -> IO PoolStats
peek = Ptr PoolStats -> IO PoolStats
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr PoolStats -> PoolStats -> IO ()
poke ptr :: Ptr PoolStats
ptr poked :: PoolStats
poked = Ptr PoolStats -> PoolStats -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr PoolStats
ptr PoolStats
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero PoolStats where
zero :: PoolStats
zero = ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> PoolStats
PoolStats
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
newtype Allocation = Allocation Word64
deriving newtype (Allocation -> Allocation -> Bool
(Allocation -> Allocation -> Bool)
-> (Allocation -> Allocation -> Bool) -> Eq Allocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Allocation -> Allocation -> Bool
$c/= :: Allocation -> Allocation -> Bool
== :: Allocation -> Allocation -> Bool
$c== :: Allocation -> Allocation -> Bool
Eq, Eq Allocation
Eq Allocation =>
(Allocation -> Allocation -> Ordering)
-> (Allocation -> Allocation -> Bool)
-> (Allocation -> Allocation -> Bool)
-> (Allocation -> Allocation -> Bool)
-> (Allocation -> Allocation -> Bool)
-> (Allocation -> Allocation -> Allocation)
-> (Allocation -> Allocation -> Allocation)
-> Ord Allocation
Allocation -> Allocation -> Bool
Allocation -> Allocation -> Ordering
Allocation -> Allocation -> Allocation
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Allocation -> Allocation -> Allocation
$cmin :: Allocation -> Allocation -> Allocation
max :: Allocation -> Allocation -> Allocation
$cmax :: Allocation -> Allocation -> Allocation
>= :: Allocation -> Allocation -> Bool
$c>= :: Allocation -> Allocation -> Bool
> :: Allocation -> Allocation -> Bool
$c> :: Allocation -> Allocation -> Bool
<= :: Allocation -> Allocation -> Bool
$c<= :: Allocation -> Allocation -> Bool
< :: Allocation -> Allocation -> Bool
$c< :: Allocation -> Allocation -> Bool
compare :: Allocation -> Allocation -> Ordering
$ccompare :: Allocation -> Allocation -> Ordering
$cp1Ord :: Eq Allocation
Ord, Ptr b -> Int -> IO Allocation
Ptr b -> Int -> Allocation -> IO ()
Ptr Allocation -> IO Allocation
Ptr Allocation -> Int -> IO Allocation
Ptr Allocation -> Int -> Allocation -> IO ()
Ptr Allocation -> Allocation -> IO ()
Allocation -> Int
(Allocation -> Int)
-> (Allocation -> Int)
-> (Ptr Allocation -> Int -> IO Allocation)
-> (Ptr Allocation -> Int -> Allocation -> IO ())
-> (forall b. Ptr b -> Int -> IO Allocation)
-> (forall b. Ptr b -> Int -> Allocation -> IO ())
-> (Ptr Allocation -> IO Allocation)
-> (Ptr Allocation -> Allocation -> IO ())
-> Storable Allocation
forall b. Ptr b -> Int -> IO Allocation
forall b. Ptr b -> Int -> Allocation -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr Allocation -> Allocation -> IO ()
$cpoke :: Ptr Allocation -> Allocation -> IO ()
peek :: Ptr Allocation -> IO Allocation
$cpeek :: Ptr Allocation -> IO Allocation
pokeByteOff :: Ptr b -> Int -> Allocation -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Allocation -> IO ()
peekByteOff :: Ptr b -> Int -> IO Allocation
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Allocation
pokeElemOff :: Ptr Allocation -> Int -> Allocation -> IO ()
$cpokeElemOff :: Ptr Allocation -> Int -> Allocation -> IO ()
peekElemOff :: Ptr Allocation -> Int -> IO Allocation
$cpeekElemOff :: Ptr Allocation -> Int -> IO Allocation
alignment :: Allocation -> Int
$calignment :: Allocation -> Int
sizeOf :: Allocation -> Int
$csizeOf :: Allocation -> Int
Storable, Allocation
Allocation -> Zero Allocation
forall a. a -> Zero a
zero :: Allocation
$czero :: Allocation
Zero)
deriving anyclass (Eq Allocation
Zero Allocation
(Eq Allocation, Zero Allocation) => IsHandle Allocation
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero Allocation
$cp1IsHandle :: Eq Allocation
IsHandle)
instance Show Allocation where
showsPrec :: Int -> Allocation -> ShowS
showsPrec p :: Int
p (Allocation x :: "lostAllocationCount" ::: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "Allocation 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("lostAllocationCount" ::: Word64) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "lostAllocationCount" ::: Word64
x)
data AllocationInfo = AllocationInfo
{
AllocationInfo -> "memoryTypeIndex" ::: Word32
memoryType :: Word32
,
AllocationInfo -> DeviceMemory
deviceMemory :: DeviceMemory
,
AllocationInfo -> "lostAllocationCount" ::: Word64
offset :: DeviceSize
,
AllocationInfo -> "lostAllocationCount" ::: Word64
size :: DeviceSize
,
AllocationInfo -> "userData" ::: Ptr ()
mappedData :: Ptr ()
,
AllocationInfo -> "userData" ::: Ptr ()
userData :: Ptr ()
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (AllocationInfo)
#endif
deriving instance Show AllocationInfo
instance ToCStruct AllocationInfo where
withCStruct :: AllocationInfo -> (Ptr AllocationInfo -> IO b) -> IO b
withCStruct x :: AllocationInfo
x f :: Ptr AllocationInfo -> IO b
f = Int -> Int -> (Ptr AllocationInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 48 8 ((Ptr AllocationInfo -> IO b) -> IO b)
-> (Ptr AllocationInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr AllocationInfo
p -> Ptr AllocationInfo -> AllocationInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AllocationInfo
p AllocationInfo
x (Ptr AllocationInfo -> IO b
f Ptr AllocationInfo
p)
pokeCStruct :: Ptr AllocationInfo -> AllocationInfo -> IO b -> IO b
pokeCStruct p :: Ptr AllocationInfo
p AllocationInfo{..} f :: IO b
f = do
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
memoryType)
Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceMemory)) (DeviceMemory
deviceMemory)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
offset)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
size)
Ptr ("userData" ::: Ptr ()) -> ("userData" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("userData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr ()))) ("userData" ::: Ptr ()
mappedData)
Ptr ("userData" ::: Ptr ()) -> ("userData" ::: Ptr ()) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("userData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr ()))) ("userData" ::: Ptr ()
userData)
IO b
f
cStructSize :: Int
cStructSize = 48
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr AllocationInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr AllocationInfo
p f :: IO b
f = do
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct AllocationInfo where
peekCStruct :: Ptr AllocationInfo -> IO AllocationInfo
peekCStruct p :: Ptr AllocationInfo
p = do
"memoryTypeIndex" ::: Word32
memoryType <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
DeviceMemory
deviceMemory <- Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceMemory))
"lostAllocationCount" ::: Word64
offset <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
size <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr DeviceSize))
"userData" ::: Ptr ()
pMappedData <- Ptr ("userData" ::: Ptr ()) -> IO ("userData" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("userData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr ())))
"userData" ::: Ptr ()
pUserData <- Ptr ("userData" ::: Ptr ()) -> IO ("userData" ::: Ptr ())
forall a. Storable a => Ptr a -> IO a
peek @(Ptr ()) ((Ptr AllocationInfo
p Ptr AllocationInfo -> Int -> Ptr ("userData" ::: Ptr ())
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr (Ptr ())))
AllocationInfo -> IO AllocationInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AllocationInfo -> IO AllocationInfo)
-> AllocationInfo -> IO AllocationInfo
forall a b. (a -> b) -> a -> b
$ ("memoryTypeIndex" ::: Word32)
-> DeviceMemory
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("userData" ::: Ptr ())
-> ("userData" ::: Ptr ())
-> AllocationInfo
AllocationInfo
"memoryTypeIndex" ::: Word32
memoryType DeviceMemory
deviceMemory "lostAllocationCount" ::: Word64
offset "lostAllocationCount" ::: Word64
size "userData" ::: Ptr ()
pMappedData "userData" ::: Ptr ()
pUserData
instance Storable AllocationInfo where
sizeOf :: AllocationInfo -> Int
sizeOf ~AllocationInfo
_ = 48
alignment :: AllocationInfo -> Int
alignment ~AllocationInfo
_ = 8
peek :: Ptr AllocationInfo -> IO AllocationInfo
peek = Ptr AllocationInfo -> IO AllocationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr AllocationInfo -> AllocationInfo -> IO ()
poke ptr :: Ptr AllocationInfo
ptr poked :: AllocationInfo
poked = Ptr AllocationInfo -> AllocationInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr AllocationInfo
ptr AllocationInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero AllocationInfo where
zero :: AllocationInfo
zero = ("memoryTypeIndex" ::: Word32)
-> DeviceMemory
-> ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("userData" ::: Ptr ())
-> ("userData" ::: Ptr ())
-> AllocationInfo
AllocationInfo
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
DeviceMemory
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"userData" ::: Ptr ()
forall a. Zero a => a
zero
"userData" ::: Ptr ()
forall a. Zero a => a
zero
newtype DefragmentationContext = DefragmentationContext Word64
deriving newtype (DefragmentationContext -> DefragmentationContext -> Bool
(DefragmentationContext -> DefragmentationContext -> Bool)
-> (DefragmentationContext -> DefragmentationContext -> Bool)
-> Eq DefragmentationContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefragmentationContext -> DefragmentationContext -> Bool
$c/= :: DefragmentationContext -> DefragmentationContext -> Bool
== :: DefragmentationContext -> DefragmentationContext -> Bool
$c== :: DefragmentationContext -> DefragmentationContext -> Bool
Eq, Eq DefragmentationContext
Eq DefragmentationContext =>
(DefragmentationContext -> DefragmentationContext -> Ordering)
-> (DefragmentationContext -> DefragmentationContext -> Bool)
-> (DefragmentationContext -> DefragmentationContext -> Bool)
-> (DefragmentationContext -> DefragmentationContext -> Bool)
-> (DefragmentationContext -> DefragmentationContext -> Bool)
-> (DefragmentationContext
-> DefragmentationContext -> DefragmentationContext)
-> (DefragmentationContext
-> DefragmentationContext -> DefragmentationContext)
-> Ord DefragmentationContext
DefragmentationContext -> DefragmentationContext -> Bool
DefragmentationContext -> DefragmentationContext -> Ordering
DefragmentationContext
-> DefragmentationContext -> DefragmentationContext
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DefragmentationContext
-> DefragmentationContext -> DefragmentationContext
$cmin :: DefragmentationContext
-> DefragmentationContext -> DefragmentationContext
max :: DefragmentationContext
-> DefragmentationContext -> DefragmentationContext
$cmax :: DefragmentationContext
-> DefragmentationContext -> DefragmentationContext
>= :: DefragmentationContext -> DefragmentationContext -> Bool
$c>= :: DefragmentationContext -> DefragmentationContext -> Bool
> :: DefragmentationContext -> DefragmentationContext -> Bool
$c> :: DefragmentationContext -> DefragmentationContext -> Bool
<= :: DefragmentationContext -> DefragmentationContext -> Bool
$c<= :: DefragmentationContext -> DefragmentationContext -> Bool
< :: DefragmentationContext -> DefragmentationContext -> Bool
$c< :: DefragmentationContext -> DefragmentationContext -> Bool
compare :: DefragmentationContext -> DefragmentationContext -> Ordering
$ccompare :: DefragmentationContext -> DefragmentationContext -> Ordering
$cp1Ord :: Eq DefragmentationContext
Ord, Ptr b -> Int -> IO DefragmentationContext
Ptr b -> Int -> DefragmentationContext -> IO ()
Ptr DefragmentationContext -> IO DefragmentationContext
Ptr DefragmentationContext -> Int -> IO DefragmentationContext
Ptr DefragmentationContext
-> Int -> DefragmentationContext -> IO ()
Ptr DefragmentationContext -> DefragmentationContext -> IO ()
DefragmentationContext -> Int
(DefragmentationContext -> Int)
-> (DefragmentationContext -> Int)
-> (Ptr DefragmentationContext -> Int -> IO DefragmentationContext)
-> (Ptr DefragmentationContext
-> Int -> DefragmentationContext -> IO ())
-> (forall b. Ptr b -> Int -> IO DefragmentationContext)
-> (forall b. Ptr b -> Int -> DefragmentationContext -> IO ())
-> (Ptr DefragmentationContext -> IO DefragmentationContext)
-> (Ptr DefragmentationContext -> DefragmentationContext -> IO ())
-> Storable DefragmentationContext
forall b. Ptr b -> Int -> IO DefragmentationContext
forall b. Ptr b -> Int -> DefragmentationContext -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr DefragmentationContext -> DefragmentationContext -> IO ()
$cpoke :: Ptr DefragmentationContext -> DefragmentationContext -> IO ()
peek :: Ptr DefragmentationContext -> IO DefragmentationContext
$cpeek :: Ptr DefragmentationContext -> IO DefragmentationContext
pokeByteOff :: Ptr b -> Int -> DefragmentationContext -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DefragmentationContext -> IO ()
peekByteOff :: Ptr b -> Int -> IO DefragmentationContext
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DefragmentationContext
pokeElemOff :: Ptr DefragmentationContext
-> Int -> DefragmentationContext -> IO ()
$cpokeElemOff :: Ptr DefragmentationContext
-> Int -> DefragmentationContext -> IO ()
peekElemOff :: Ptr DefragmentationContext -> Int -> IO DefragmentationContext
$cpeekElemOff :: Ptr DefragmentationContext -> Int -> IO DefragmentationContext
alignment :: DefragmentationContext -> Int
$calignment :: DefragmentationContext -> Int
sizeOf :: DefragmentationContext -> Int
$csizeOf :: DefragmentationContext -> Int
Storable, DefragmentationContext
DefragmentationContext -> Zero DefragmentationContext
forall a. a -> Zero a
zero :: DefragmentationContext
$czero :: DefragmentationContext
Zero)
deriving anyclass (Eq DefragmentationContext
Zero DefragmentationContext
(Eq DefragmentationContext, Zero DefragmentationContext) =>
IsHandle DefragmentationContext
forall a. (Eq a, Zero a) => IsHandle a
$cp2IsHandle :: Zero DefragmentationContext
$cp1IsHandle :: Eq DefragmentationContext
IsHandle)
instance Show DefragmentationContext where
showsPrec :: Int -> DefragmentationContext -> ShowS
showsPrec p :: Int
p (DefragmentationContext x :: "lostAllocationCount" ::: Word64
x) = Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DefragmentationContext 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("lostAllocationCount" ::: Word64) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "lostAllocationCount" ::: Word64
x)
newtype DefragmentationFlagBits = DefragmentationFlagBits Flags
deriving newtype (DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
(DefragmentationFlagBits -> DefragmentationFlagBits -> Bool)
-> (DefragmentationFlagBits -> DefragmentationFlagBits -> Bool)
-> Eq DefragmentationFlagBits
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
$c/= :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
== :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
$c== :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
Eq, Eq DefragmentationFlagBits
Eq DefragmentationFlagBits =>
(DefragmentationFlagBits -> DefragmentationFlagBits -> Ordering)
-> (DefragmentationFlagBits -> DefragmentationFlagBits -> Bool)
-> (DefragmentationFlagBits -> DefragmentationFlagBits -> Bool)
-> (DefragmentationFlagBits -> DefragmentationFlagBits -> Bool)
-> (DefragmentationFlagBits -> DefragmentationFlagBits -> Bool)
-> (DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits)
-> (DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits)
-> Ord DefragmentationFlagBits
DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
DefragmentationFlagBits -> DefragmentationFlagBits -> Ordering
DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
$cmin :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
max :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
$cmax :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
>= :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
$c>= :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
> :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
$c> :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
<= :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
$c<= :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
< :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
$c< :: DefragmentationFlagBits -> DefragmentationFlagBits -> Bool
compare :: DefragmentationFlagBits -> DefragmentationFlagBits -> Ordering
$ccompare :: DefragmentationFlagBits -> DefragmentationFlagBits -> Ordering
$cp1Ord :: Eq DefragmentationFlagBits
Ord, Ptr b -> Int -> IO DefragmentationFlagBits
Ptr b -> Int -> DefragmentationFlagBits -> IO ()
Ptr DefragmentationFlagBits -> IO DefragmentationFlagBits
Ptr DefragmentationFlagBits -> Int -> IO DefragmentationFlagBits
Ptr DefragmentationFlagBits
-> Int -> DefragmentationFlagBits -> IO ()
Ptr DefragmentationFlagBits -> DefragmentationFlagBits -> IO ()
DefragmentationFlagBits -> Int
(DefragmentationFlagBits -> Int)
-> (DefragmentationFlagBits -> Int)
-> (Ptr DefragmentationFlagBits
-> Int -> IO DefragmentationFlagBits)
-> (Ptr DefragmentationFlagBits
-> Int -> DefragmentationFlagBits -> IO ())
-> (forall b. Ptr b -> Int -> IO DefragmentationFlagBits)
-> (forall b. Ptr b -> Int -> DefragmentationFlagBits -> IO ())
-> (Ptr DefragmentationFlagBits -> IO DefragmentationFlagBits)
-> (Ptr DefragmentationFlagBits
-> DefragmentationFlagBits -> IO ())
-> Storable DefragmentationFlagBits
forall b. Ptr b -> Int -> IO DefragmentationFlagBits
forall b. Ptr b -> Int -> DefragmentationFlagBits -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr DefragmentationFlagBits -> DefragmentationFlagBits -> IO ()
$cpoke :: Ptr DefragmentationFlagBits -> DefragmentationFlagBits -> IO ()
peek :: Ptr DefragmentationFlagBits -> IO DefragmentationFlagBits
$cpeek :: Ptr DefragmentationFlagBits -> IO DefragmentationFlagBits
pokeByteOff :: Ptr b -> Int -> DefragmentationFlagBits -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> DefragmentationFlagBits -> IO ()
peekByteOff :: Ptr b -> Int -> IO DefragmentationFlagBits
$cpeekByteOff :: forall b. Ptr b -> Int -> IO DefragmentationFlagBits
pokeElemOff :: Ptr DefragmentationFlagBits
-> Int -> DefragmentationFlagBits -> IO ()
$cpokeElemOff :: Ptr DefragmentationFlagBits
-> Int -> DefragmentationFlagBits -> IO ()
peekElemOff :: Ptr DefragmentationFlagBits -> Int -> IO DefragmentationFlagBits
$cpeekElemOff :: Ptr DefragmentationFlagBits -> Int -> IO DefragmentationFlagBits
alignment :: DefragmentationFlagBits -> Int
$calignment :: DefragmentationFlagBits -> Int
sizeOf :: DefragmentationFlagBits -> Int
$csizeOf :: DefragmentationFlagBits -> Int
Storable, DefragmentationFlagBits
DefragmentationFlagBits -> Zero DefragmentationFlagBits
forall a. a -> Zero a
zero :: DefragmentationFlagBits
$czero :: DefragmentationFlagBits
Zero, Eq DefragmentationFlagBits
DefragmentationFlagBits
Eq DefragmentationFlagBits =>
(DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits)
-> (DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits)
-> (DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> DefragmentationFlagBits
-> (Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> Bool)
-> (DefragmentationFlagBits -> Maybe Int)
-> (DefragmentationFlagBits -> Int)
-> (DefragmentationFlagBits -> Bool)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int -> DefragmentationFlagBits)
-> (DefragmentationFlagBits -> Int)
-> Bits DefragmentationFlagBits
Int -> DefragmentationFlagBits
DefragmentationFlagBits -> Bool
DefragmentationFlagBits -> Int
DefragmentationFlagBits -> Maybe Int
DefragmentationFlagBits -> DefragmentationFlagBits
DefragmentationFlagBits -> Int -> Bool
DefragmentationFlagBits -> Int -> DefragmentationFlagBits
DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: DefragmentationFlagBits -> Int
$cpopCount :: DefragmentationFlagBits -> Int
rotateR :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$crotateR :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
rotateL :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$crotateL :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
unsafeShiftR :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$cunsafeShiftR :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
shiftR :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$cshiftR :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
unsafeShiftL :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$cunsafeShiftL :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
shiftL :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$cshiftL :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
isSigned :: DefragmentationFlagBits -> Bool
$cisSigned :: DefragmentationFlagBits -> Bool
bitSize :: DefragmentationFlagBits -> Int
$cbitSize :: DefragmentationFlagBits -> Int
bitSizeMaybe :: DefragmentationFlagBits -> Maybe Int
$cbitSizeMaybe :: DefragmentationFlagBits -> Maybe Int
testBit :: DefragmentationFlagBits -> Int -> Bool
$ctestBit :: DefragmentationFlagBits -> Int -> Bool
complementBit :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$ccomplementBit :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
clearBit :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$cclearBit :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
setBit :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$csetBit :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
bit :: Int -> DefragmentationFlagBits
$cbit :: Int -> DefragmentationFlagBits
zeroBits :: DefragmentationFlagBits
$czeroBits :: DefragmentationFlagBits
rotate :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$crotate :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
shift :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
$cshift :: DefragmentationFlagBits -> Int -> DefragmentationFlagBits
complement :: DefragmentationFlagBits -> DefragmentationFlagBits
$ccomplement :: DefragmentationFlagBits -> DefragmentationFlagBits
xor :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
$cxor :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
.|. :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
$c.|. :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
.&. :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
$c.&. :: DefragmentationFlagBits
-> DefragmentationFlagBits -> DefragmentationFlagBits
$cp1Bits :: Eq DefragmentationFlagBits
Bits)
pattern $bDEFRAGMENTATION_FLAG_INCREMENTAL :: DefragmentationFlagBits
$mDEFRAGMENTATION_FLAG_INCREMENTAL :: forall r.
DefragmentationFlagBits -> (Void# -> r) -> (Void# -> r) -> r
DEFRAGMENTATION_FLAG_INCREMENTAL = DefragmentationFlagBits 0x00000001
type DefragmentationFlags = DefragmentationFlagBits
instance Show DefragmentationFlagBits where
showsPrec :: Int -> DefragmentationFlagBits -> ShowS
showsPrec p :: Int
p = \case
DEFRAGMENTATION_FLAG_INCREMENTAL -> String -> ShowS
showString "DEFRAGMENTATION_FLAG_INCREMENTAL"
DefragmentationFlagBits x :: "memoryTypeIndex" ::: Word32
x -> Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= 11) (String -> ShowS
showString "DefragmentationFlagBits 0x" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ("memoryTypeIndex" ::: Word32) -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showHex "memoryTypeIndex" ::: Word32
x)
instance Read DefragmentationFlagBits where
readPrec :: ReadPrec DefragmentationFlagBits
readPrec = ReadPrec DefragmentationFlagBits
-> ReadPrec DefragmentationFlagBits
forall a. ReadPrec a -> ReadPrec a
parens ([(String, ReadPrec DefragmentationFlagBits)]
-> ReadPrec DefragmentationFlagBits
forall a. [(String, ReadPrec a)] -> ReadPrec a
choose [("DEFRAGMENTATION_FLAG_INCREMENTAL", DefragmentationFlagBits -> ReadPrec DefragmentationFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefragmentationFlagBits
DEFRAGMENTATION_FLAG_INCREMENTAL)]
ReadPrec DefragmentationFlagBits
-> ReadPrec DefragmentationFlagBits
-> ReadPrec DefragmentationFlagBits
forall a. ReadPrec a -> ReadPrec a -> ReadPrec a
+++
Int
-> ReadPrec DefragmentationFlagBits
-> ReadPrec DefragmentationFlagBits
forall a. Int -> ReadPrec a -> ReadPrec a
prec 10 (do
Lexeme -> ReadPrec ()
expectP (String -> Lexeme
Ident "DefragmentationFlagBits")
"memoryTypeIndex" ::: Word32
v <- ReadPrec ("memoryTypeIndex" ::: Word32)
-> ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. ReadPrec a -> ReadPrec a
step ReadPrec ("memoryTypeIndex" ::: Word32)
forall a. Read a => ReadPrec a
readPrec
DefragmentationFlagBits -> ReadPrec DefragmentationFlagBits
forall (f :: * -> *) a. Applicative f => a -> f a
pure (("memoryTypeIndex" ::: Word32) -> DefragmentationFlagBits
DefragmentationFlagBits "memoryTypeIndex" ::: Word32
v)))
data DefragmentationInfo2 = DefragmentationInfo2
{
DefragmentationInfo2 -> DefragmentationFlagBits
flags :: DefragmentationFlags
,
DefragmentationInfo2 -> "allocations" ::: Vector Allocation
allocations :: Vector Allocation
,
DefragmentationInfo2 -> Ptr Bool32
allocationsChanged :: Ptr Bool32
,
DefragmentationInfo2 -> Vector Pool
pools :: Vector Pool
,
DefragmentationInfo2 -> "lostAllocationCount" ::: Word64
maxCpuBytesToMove :: DeviceSize
,
DefragmentationInfo2 -> "memoryTypeIndex" ::: Word32
maxCpuAllocationsToMove :: Word32
,
DefragmentationInfo2 -> "lostAllocationCount" ::: Word64
maxGpuBytesToMove :: DeviceSize
,
DefragmentationInfo2 -> "memoryTypeIndex" ::: Word32
maxGpuAllocationsToMove :: Word32
,
DefragmentationInfo2 -> Ptr CommandBuffer_T
commandBuffer :: Ptr CommandBuffer_T
}
deriving (Typeable)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DefragmentationInfo2)
#endif
deriving instance Show DefragmentationInfo2
instance ToCStruct DefragmentationInfo2 where
withCStruct :: DefragmentationInfo2 -> (Ptr DefragmentationInfo2 -> IO b) -> IO b
withCStruct x :: DefragmentationInfo2
x f :: Ptr DefragmentationInfo2 -> IO b
f = Int -> Int -> (Ptr DefragmentationInfo2 -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 80 8 ((Ptr DefragmentationInfo2 -> IO b) -> IO b)
-> (Ptr DefragmentationInfo2 -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DefragmentationInfo2
p -> Ptr DefragmentationInfo2 -> DefragmentationInfo2 -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DefragmentationInfo2
p DefragmentationInfo2
x (Ptr DefragmentationInfo2 -> IO b
f Ptr DefragmentationInfo2
p)
pokeCStruct :: Ptr DefragmentationInfo2 -> DefragmentationInfo2 -> IO b -> IO b
pokeCStruct p :: Ptr DefragmentationInfo2
p DefragmentationInfo2{..} 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 DefragmentationFlagBits -> DefragmentationFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr DefragmentationFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DefragmentationFlags)) (DefragmentationFlagBits
flags)
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 ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32)) ((Int -> "memoryTypeIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length (("allocations" ::: Vector Allocation) -> Int)
-> ("allocations" ::: Vector Allocation) -> Int
forall a b. (a -> b) -> a -> b
$ ("allocations" ::: Vector Allocation
allocations)) :: Word32))
Ptr Allocation
pPAllocations' <- ((Ptr Allocation -> IO b) -> IO b) -> ContT b IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO b) -> IO b) -> ContT b IO (Ptr Allocation))
-> ((Ptr Allocation -> IO b) -> IO b)
-> ContT b IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Allocation -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Allocation ((("allocations" ::: Vector Allocation) -> Int
forall a. Vector a -> Int
Data.Vector.length ("allocations" ::: Vector Allocation
allocations)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
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
$ (Int -> Allocation -> IO ())
-> ("allocations" ::: Vector Allocation) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Allocation
e -> Ptr Allocation -> Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Allocation
pPAllocations' Ptr Allocation -> Int -> Ptr Allocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Allocation) (Allocation
e)) ("allocations" ::: Vector Allocation
allocations)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Allocation) -> Ptr Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr Allocation)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr Allocation))) (Ptr Allocation
pPAllocations')
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Bool32) -> Ptr Bool32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr Bool32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr Bool32))) (Ptr Bool32
allocationsChanged)
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 ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32)) ((Int -> "memoryTypeIndex" ::: Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Vector Pool -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Pool -> Int) -> Vector Pool -> Int
forall a b. (a -> b) -> a -> b
$ (Vector Pool
pools)) :: Word32))
Ptr Pool
pPPools' <- ((Ptr Pool -> IO b) -> IO b) -> ContT b IO (Ptr Pool)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Pool -> IO b) -> IO b) -> ContT b IO (Ptr Pool))
-> ((Ptr Pool -> IO b) -> IO b) -> ContT b IO (Ptr Pool)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Pool -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Pool ((Vector Pool -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Pool
pools)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
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
$ (Int -> Pool -> IO ()) -> Vector Pool -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Pool
e -> Ptr Pool -> Pool -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Pool
pPPools' Ptr Pool -> Int -> Ptr Pool
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Pool) (Pool
e)) (Vector Pool
pools)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Pool) -> Ptr Pool -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr Pool)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr Pool))) (Ptr Pool
pPPools')
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 ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
maxCpuBytesToMove)
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 ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
maxCpuAllocationsToMove)
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 ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
maxGpuBytesToMove)
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 ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
maxGpuAllocationsToMove)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr CommandBuffer_T) -> Ptr CommandBuffer_T -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr CommandBuffer_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr CommandBuffer_T))) (Ptr CommandBuffer_T
commandBuffer)
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 = 80
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr DefragmentationInfo2 -> IO b -> IO b
pokeZeroCStruct p :: Ptr DefragmentationInfo2
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 DefragmentationFlagBits -> DefragmentationFlagBits -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr DefragmentationFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DefragmentationFlags)) (DefragmentationFlagBits
forall a. Zero a => a
zero)
Ptr Allocation
pPAllocations' <- ((Ptr Allocation -> IO b) -> IO b) -> ContT b IO (Ptr Allocation)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Allocation -> IO b) -> IO b) -> ContT b IO (Ptr Allocation))
-> ((Ptr Allocation -> IO b) -> IO b)
-> ContT b IO (Ptr Allocation)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Allocation -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Allocation ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
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
$ (Int -> Allocation -> IO ())
-> ("allocations" ::: Vector Allocation) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Allocation
e -> Ptr Allocation -> Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Allocation
pPAllocations' Ptr Allocation -> Int -> Ptr Allocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Allocation) (Allocation
e)) ("allocations" ::: Vector Allocation
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Allocation) -> Ptr Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr Allocation)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr Allocation))) (Ptr Allocation
pPAllocations')
Ptr Pool
pPPools' <- ((Ptr Pool -> IO b) -> IO b) -> ContT b IO (Ptr Pool)
forall k (r :: k) (m :: k -> *) a.
((a -> m r) -> m r) -> ContT r m a
ContT (((Ptr Pool -> IO b) -> IO b) -> ContT b IO (Ptr Pool))
-> ((Ptr Pool -> IO b) -> IO b) -> ContT b IO (Ptr Pool)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> (Ptr Pool -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned @Pool ((Vector Any -> Int
forall a. Vector a -> Int
Data.Vector.length (Vector Any
forall a. Monoid a => a
mempty)) Int -> Int -> Int
forall a. Num a => a -> a -> a
* 8) 8
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
$ (Int -> Pool -> IO ()) -> Vector Pool -> IO ()
forall (m :: * -> *) a b.
Monad m =>
(Int -> a -> m b) -> Vector a -> m ()
Data.Vector.imapM_ (\i :: Int
i e :: Pool
e -> Ptr Pool -> Pool -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Pool
pPPools' Ptr Pool -> Int -> Ptr Pool
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Pool) (Pool
e)) (Vector Pool
forall a. Monoid a => a
mempty)
IO () -> ContT b IO ()
forall (t :: (* -> *) -> * -> *) (m :: * -> *) a.
(MonadTrans t, Monad m) =>
m a -> t m a
lift (IO () -> ContT b IO ()) -> IO () -> ContT b IO ()
forall a b. (a -> b) -> a -> b
$ Ptr (Ptr Pool) -> Ptr Pool -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr Pool)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr Pool))) (Ptr Pool
pPPools')
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 ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
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 ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
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 ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
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 ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32)) ("memoryTypeIndex" ::: 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 FromCStruct DefragmentationInfo2 where
peekCStruct :: Ptr DefragmentationInfo2 -> IO DefragmentationInfo2
peekCStruct p :: Ptr DefragmentationInfo2
p = do
DefragmentationFlagBits
flags <- Ptr DefragmentationFlagBits -> IO DefragmentationFlagBits
forall a. Storable a => Ptr a -> IO a
peek @DefragmentationFlags ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr DefragmentationFlagBits
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DefragmentationFlags))
"memoryTypeIndex" ::: Word32
allocationCount <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 4 :: Ptr Word32))
Ptr Allocation
pAllocations <- Ptr (Ptr Allocation) -> IO (Ptr Allocation)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Allocation) ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr Allocation)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr Allocation)))
"allocations" ::: Vector Allocation
pAllocations' <- Int
-> (Int -> IO Allocation)
-> IO ("allocations" ::: Vector Allocation)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("memoryTypeIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "memoryTypeIndex" ::: Word32
allocationCount) (\i :: Int
i -> Ptr Allocation -> IO Allocation
forall a. Storable a => Ptr a -> IO a
peek @Allocation ((Ptr Allocation
pAllocations Ptr Allocation -> Int -> Ptr Allocation
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Allocation)))
Ptr Bool32
pAllocationsChanged <- Ptr (Ptr Bool32) -> IO (Ptr Bool32)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Bool32) ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr Bool32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr (Ptr Bool32)))
"memoryTypeIndex" ::: Word32
poolCount <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24 :: Ptr Word32))
Ptr Pool
pPools <- Ptr (Ptr Pool) -> IO (Ptr Pool)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr Pool) ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr Pool)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32 :: Ptr (Ptr Pool)))
Vector Pool
pPools' <- Int -> (Int -> IO Pool) -> IO (Vector Pool)
forall (m :: * -> *) a.
Monad m =>
Int -> (Int -> m a) -> m (Vector a)
generateM (("memoryTypeIndex" ::: Word32) -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral "memoryTypeIndex" ::: Word32
poolCount) (\i :: Int
i -> Ptr Pool -> IO Pool
forall a. Storable a => Ptr a -> IO a
peek @Pool ((Ptr Pool
pPools Ptr Pool -> Int -> Ptr Pool
forall a. Ptr a -> Int -> Ptr a
`advancePtrBytes` (8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* (Int
i)) :: Ptr Pool)))
"lostAllocationCount" ::: Word64
maxCpuBytesToMove <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 40 :: Ptr DeviceSize))
"memoryTypeIndex" ::: Word32
maxCpuAllocationsToMove <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 48 :: Ptr Word32))
"lostAllocationCount" ::: Word64
maxGpuBytesToMove <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 56 :: Ptr DeviceSize))
"memoryTypeIndex" ::: Word32
maxGpuAllocationsToMove <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 64 :: Ptr Word32))
Ptr CommandBuffer_T
commandBuffer <- Ptr (Ptr CommandBuffer_T) -> IO (Ptr CommandBuffer_T)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr CommandBuffer_T) ((Ptr DefragmentationInfo2
p Ptr DefragmentationInfo2 -> Int -> Ptr (Ptr CommandBuffer_T)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 72 :: Ptr (Ptr CommandBuffer_T)))
DefragmentationInfo2 -> IO DefragmentationInfo2
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DefragmentationInfo2 -> IO DefragmentationInfo2)
-> DefragmentationInfo2 -> IO DefragmentationInfo2
forall a b. (a -> b) -> a -> b
$ DefragmentationFlagBits
-> ("allocations" ::: Vector Allocation)
-> Ptr Bool32
-> Vector Pool
-> ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32)
-> ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32)
-> Ptr CommandBuffer_T
-> DefragmentationInfo2
DefragmentationInfo2
DefragmentationFlagBits
flags "allocations" ::: Vector Allocation
pAllocations' Ptr Bool32
pAllocationsChanged Vector Pool
pPools' "lostAllocationCount" ::: Word64
maxCpuBytesToMove "memoryTypeIndex" ::: Word32
maxCpuAllocationsToMove "lostAllocationCount" ::: Word64
maxGpuBytesToMove "memoryTypeIndex" ::: Word32
maxGpuAllocationsToMove Ptr CommandBuffer_T
commandBuffer
instance Zero DefragmentationInfo2 where
zero :: DefragmentationInfo2
zero = DefragmentationFlagBits
-> ("allocations" ::: Vector Allocation)
-> Ptr Bool32
-> Vector Pool
-> ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32)
-> ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32)
-> Ptr CommandBuffer_T
-> DefragmentationInfo2
DefragmentationInfo2
DefragmentationFlagBits
forall a. Zero a => a
zero
"allocations" ::: Vector Allocation
forall a. Monoid a => a
mempty
Ptr Bool32
forall a. Zero a => a
zero
Vector Pool
forall a. Monoid a => a
mempty
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
Ptr CommandBuffer_T
forall a. Zero a => a
zero
data DefragmentationPassMoveInfo = DefragmentationPassMoveInfo
{
DefragmentationPassMoveInfo -> Allocation
allocation :: Allocation
,
DefragmentationPassMoveInfo -> DeviceMemory
memory :: DeviceMemory
,
DefragmentationPassMoveInfo -> "lostAllocationCount" ::: Word64
offset :: DeviceSize
}
deriving (Typeable, DefragmentationPassMoveInfo -> DefragmentationPassMoveInfo -> Bool
(DefragmentationPassMoveInfo
-> DefragmentationPassMoveInfo -> Bool)
-> (DefragmentationPassMoveInfo
-> DefragmentationPassMoveInfo -> Bool)
-> Eq DefragmentationPassMoveInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefragmentationPassMoveInfo -> DefragmentationPassMoveInfo -> Bool
$c/= :: DefragmentationPassMoveInfo -> DefragmentationPassMoveInfo -> Bool
== :: DefragmentationPassMoveInfo -> DefragmentationPassMoveInfo -> Bool
$c== :: DefragmentationPassMoveInfo -> DefragmentationPassMoveInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DefragmentationPassMoveInfo)
#endif
deriving instance Show DefragmentationPassMoveInfo
instance ToCStruct DefragmentationPassMoveInfo where
withCStruct :: DefragmentationPassMoveInfo
-> (Ptr DefragmentationPassMoveInfo -> IO b) -> IO b
withCStruct x :: DefragmentationPassMoveInfo
x f :: Ptr DefragmentationPassMoveInfo -> IO b
f = Int -> Int -> (Ptr DefragmentationPassMoveInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DefragmentationPassMoveInfo -> IO b) -> IO b)
-> (Ptr DefragmentationPassMoveInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DefragmentationPassMoveInfo
p -> Ptr DefragmentationPassMoveInfo
-> DefragmentationPassMoveInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DefragmentationPassMoveInfo
p DefragmentationPassMoveInfo
x (Ptr DefragmentationPassMoveInfo -> IO b
f Ptr DefragmentationPassMoveInfo
p)
pokeCStruct :: Ptr DefragmentationPassMoveInfo
-> DefragmentationPassMoveInfo -> IO b -> IO b
pokeCStruct p :: Ptr DefragmentationPassMoveInfo
p DefragmentationPassMoveInfo{..} f :: IO b
f = do
Ptr Allocation -> Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassMoveInfo
p Ptr DefragmentationPassMoveInfo -> Int -> Ptr Allocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Allocation)) (Allocation
allocation)
Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassMoveInfo
p Ptr DefragmentationPassMoveInfo -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceMemory)) (DeviceMemory
memory)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassMoveInfo
p Ptr DefragmentationPassMoveInfo
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
offset)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr DefragmentationPassMoveInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr DefragmentationPassMoveInfo
p f :: IO b
f = do
Ptr Allocation -> Allocation -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassMoveInfo
p Ptr DefragmentationPassMoveInfo -> Int -> Ptr Allocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Allocation)) (Allocation
forall a. Zero a => a
zero)
Ptr DeviceMemory -> DeviceMemory -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassMoveInfo
p Ptr DefragmentationPassMoveInfo -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceMemory)) (DeviceMemory
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassMoveInfo
p Ptr DefragmentationPassMoveInfo
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DefragmentationPassMoveInfo where
peekCStruct :: Ptr DefragmentationPassMoveInfo -> IO DefragmentationPassMoveInfo
peekCStruct p :: Ptr DefragmentationPassMoveInfo
p = do
Allocation
allocation <- Ptr Allocation -> IO Allocation
forall a. Storable a => Ptr a -> IO a
peek @Allocation ((Ptr DefragmentationPassMoveInfo
p Ptr DefragmentationPassMoveInfo -> Int -> Ptr Allocation
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Allocation))
DeviceMemory
memory <- Ptr DeviceMemory -> IO DeviceMemory
forall a. Storable a => Ptr a -> IO a
peek @DeviceMemory ((Ptr DefragmentationPassMoveInfo
p Ptr DefragmentationPassMoveInfo -> Int -> Ptr DeviceMemory
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceMemory))
"lostAllocationCount" ::: Word64
offset <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr DefragmentationPassMoveInfo
p Ptr DefragmentationPassMoveInfo
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr DeviceSize))
DefragmentationPassMoveInfo -> IO DefragmentationPassMoveInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DefragmentationPassMoveInfo -> IO DefragmentationPassMoveInfo)
-> DefragmentationPassMoveInfo -> IO DefragmentationPassMoveInfo
forall a b. (a -> b) -> a -> b
$ Allocation
-> DeviceMemory
-> ("lostAllocationCount" ::: Word64)
-> DefragmentationPassMoveInfo
DefragmentationPassMoveInfo
Allocation
allocation DeviceMemory
memory "lostAllocationCount" ::: Word64
offset
instance Storable DefragmentationPassMoveInfo where
sizeOf :: DefragmentationPassMoveInfo -> Int
sizeOf ~DefragmentationPassMoveInfo
_ = 24
alignment :: DefragmentationPassMoveInfo -> Int
alignment ~DefragmentationPassMoveInfo
_ = 8
peek :: Ptr DefragmentationPassMoveInfo -> IO DefragmentationPassMoveInfo
peek = Ptr DefragmentationPassMoveInfo -> IO DefragmentationPassMoveInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DefragmentationPassMoveInfo
-> DefragmentationPassMoveInfo -> IO ()
poke ptr :: Ptr DefragmentationPassMoveInfo
ptr poked :: DefragmentationPassMoveInfo
poked = Ptr DefragmentationPassMoveInfo
-> DefragmentationPassMoveInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DefragmentationPassMoveInfo
ptr DefragmentationPassMoveInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DefragmentationPassMoveInfo where
zero :: DefragmentationPassMoveInfo
zero = Allocation
-> DeviceMemory
-> ("lostAllocationCount" ::: Word64)
-> DefragmentationPassMoveInfo
DefragmentationPassMoveInfo
Allocation
forall a. Zero a => a
zero
DeviceMemory
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
data DefragmentationPassInfo = DefragmentationPassInfo
{
DefragmentationPassInfo -> "memoryTypeIndex" ::: Word32
moveCount :: Word32
,
DefragmentationPassInfo -> Ptr DefragmentationPassMoveInfo
moves :: Ptr DefragmentationPassMoveInfo
}
deriving (Typeable, DefragmentationPassInfo -> DefragmentationPassInfo -> Bool
(DefragmentationPassInfo -> DefragmentationPassInfo -> Bool)
-> (DefragmentationPassInfo -> DefragmentationPassInfo -> Bool)
-> Eq DefragmentationPassInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefragmentationPassInfo -> DefragmentationPassInfo -> Bool
$c/= :: DefragmentationPassInfo -> DefragmentationPassInfo -> Bool
== :: DefragmentationPassInfo -> DefragmentationPassInfo -> Bool
$c== :: DefragmentationPassInfo -> DefragmentationPassInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DefragmentationPassInfo)
#endif
deriving instance Show DefragmentationPassInfo
instance ToCStruct DefragmentationPassInfo where
withCStruct :: DefragmentationPassInfo
-> (Ptr DefragmentationPassInfo -> IO b) -> IO b
withCStruct x :: DefragmentationPassInfo
x f :: Ptr DefragmentationPassInfo -> IO b
f = Int -> Int -> (Ptr DefragmentationPassInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 8 ((Ptr DefragmentationPassInfo -> IO b) -> IO b)
-> (Ptr DefragmentationPassInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DefragmentationPassInfo
p -> Ptr DefragmentationPassInfo
-> DefragmentationPassInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DefragmentationPassInfo
p DefragmentationPassInfo
x (Ptr DefragmentationPassInfo -> IO b
f Ptr DefragmentationPassInfo
p)
pokeCStruct :: Ptr DefragmentationPassInfo
-> DefragmentationPassInfo -> IO b -> IO b
pokeCStruct p :: Ptr DefragmentationPassInfo
p DefragmentationPassInfo{..} f :: IO b
f = do
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassInfo
p Ptr DefragmentationPassInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
moveCount)
Ptr (Ptr DefragmentationPassMoveInfo)
-> Ptr DefragmentationPassMoveInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassInfo
p Ptr DefragmentationPassInfo
-> Int -> Ptr (Ptr DefragmentationPassMoveInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr DefragmentationPassMoveInfo))) (Ptr DefragmentationPassMoveInfo
moves)
IO b
f
cStructSize :: Int
cStructSize = 16
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr DefragmentationPassInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr DefragmentationPassInfo
p f :: IO b
f = do
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassInfo
p Ptr DefragmentationPassInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
Ptr (Ptr DefragmentationPassMoveInfo)
-> Ptr DefragmentationPassMoveInfo -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationPassInfo
p Ptr DefragmentationPassInfo
-> Int -> Ptr (Ptr DefragmentationPassMoveInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr DefragmentationPassMoveInfo))) (Ptr DefragmentationPassMoveInfo
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DefragmentationPassInfo where
peekCStruct :: Ptr DefragmentationPassInfo -> IO DefragmentationPassInfo
peekCStruct p :: Ptr DefragmentationPassInfo
p = do
"memoryTypeIndex" ::: Word32
moveCount <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DefragmentationPassInfo
p Ptr DefragmentationPassInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr Word32))
Ptr DefragmentationPassMoveInfo
pMoves <- Ptr (Ptr DefragmentationPassMoveInfo)
-> IO (Ptr DefragmentationPassMoveInfo)
forall a. Storable a => Ptr a -> IO a
peek @(Ptr DefragmentationPassMoveInfo) ((Ptr DefragmentationPassInfo
p Ptr DefragmentationPassInfo
-> Int -> Ptr (Ptr DefragmentationPassMoveInfo)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr (Ptr DefragmentationPassMoveInfo)))
DefragmentationPassInfo -> IO DefragmentationPassInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DefragmentationPassInfo -> IO DefragmentationPassInfo)
-> DefragmentationPassInfo -> IO DefragmentationPassInfo
forall a b. (a -> b) -> a -> b
$ ("memoryTypeIndex" ::: Word32)
-> Ptr DefragmentationPassMoveInfo -> DefragmentationPassInfo
DefragmentationPassInfo
"memoryTypeIndex" ::: Word32
moveCount Ptr DefragmentationPassMoveInfo
pMoves
instance Storable DefragmentationPassInfo where
sizeOf :: DefragmentationPassInfo -> Int
sizeOf ~DefragmentationPassInfo
_ = 16
alignment :: DefragmentationPassInfo -> Int
alignment ~DefragmentationPassInfo
_ = 8
peek :: Ptr DefragmentationPassInfo -> IO DefragmentationPassInfo
peek = Ptr DefragmentationPassInfo -> IO DefragmentationPassInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DefragmentationPassInfo -> DefragmentationPassInfo -> IO ()
poke ptr :: Ptr DefragmentationPassInfo
ptr poked :: DefragmentationPassInfo
poked = Ptr DefragmentationPassInfo
-> DefragmentationPassInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DefragmentationPassInfo
ptr DefragmentationPassInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DefragmentationPassInfo where
zero :: DefragmentationPassInfo
zero = ("memoryTypeIndex" ::: Word32)
-> Ptr DefragmentationPassMoveInfo -> DefragmentationPassInfo
DefragmentationPassInfo
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
Ptr DefragmentationPassMoveInfo
forall a. Zero a => a
zero
data DefragmentationInfo = DefragmentationInfo
{
DefragmentationInfo -> "lostAllocationCount" ::: Word64
maxBytesToMove :: DeviceSize
,
DefragmentationInfo -> "memoryTypeIndex" ::: Word32
maxAllocationsToMove :: Word32
}
deriving (Typeable, DefragmentationInfo -> DefragmentationInfo -> Bool
(DefragmentationInfo -> DefragmentationInfo -> Bool)
-> (DefragmentationInfo -> DefragmentationInfo -> Bool)
-> Eq DefragmentationInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefragmentationInfo -> DefragmentationInfo -> Bool
$c/= :: DefragmentationInfo -> DefragmentationInfo -> Bool
== :: DefragmentationInfo -> DefragmentationInfo -> Bool
$c== :: DefragmentationInfo -> DefragmentationInfo -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DefragmentationInfo)
#endif
deriving instance Show DefragmentationInfo
instance ToCStruct DefragmentationInfo where
withCStruct :: DefragmentationInfo -> (Ptr DefragmentationInfo -> IO b) -> IO b
withCStruct x :: DefragmentationInfo
x f :: Ptr DefragmentationInfo -> IO b
f = Int -> Int -> (Ptr DefragmentationInfo -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 16 8 ((Ptr DefragmentationInfo -> IO b) -> IO b)
-> (Ptr DefragmentationInfo -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DefragmentationInfo
p -> Ptr DefragmentationInfo -> DefragmentationInfo -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DefragmentationInfo
p DefragmentationInfo
x (Ptr DefragmentationInfo -> IO b
f Ptr DefragmentationInfo
p)
pokeCStruct :: Ptr DefragmentationInfo -> DefragmentationInfo -> IO b -> IO b
pokeCStruct p :: Ptr DefragmentationInfo
p DefragmentationInfo{..} f :: IO b
f = do
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo
p Ptr DefragmentationInfo
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
maxBytesToMove)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo
p Ptr DefragmentationInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
maxAllocationsToMove)
IO b
f
cStructSize :: Int
cStructSize = 16
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr DefragmentationInfo -> IO b -> IO b
pokeZeroCStruct p :: Ptr DefragmentationInfo
p f :: IO b
f = do
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo
p Ptr DefragmentationInfo
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationInfo
p Ptr DefragmentationInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DefragmentationInfo where
peekCStruct :: Ptr DefragmentationInfo -> IO DefragmentationInfo
peekCStruct p :: Ptr DefragmentationInfo
p = do
"lostAllocationCount" ::: Word64
maxBytesToMove <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr DefragmentationInfo
p Ptr DefragmentationInfo
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize))
"memoryTypeIndex" ::: Word32
maxAllocationsToMove <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DefragmentationInfo
p Ptr DefragmentationInfo
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr Word32))
DefragmentationInfo -> IO DefragmentationInfo
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DefragmentationInfo -> IO DefragmentationInfo)
-> DefragmentationInfo -> IO DefragmentationInfo
forall a b. (a -> b) -> a -> b
$ ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32) -> DefragmentationInfo
DefragmentationInfo
"lostAllocationCount" ::: Word64
maxBytesToMove "memoryTypeIndex" ::: Word32
maxAllocationsToMove
instance Storable DefragmentationInfo where
sizeOf :: DefragmentationInfo -> Int
sizeOf ~DefragmentationInfo
_ = 16
alignment :: DefragmentationInfo -> Int
alignment ~DefragmentationInfo
_ = 8
peek :: Ptr DefragmentationInfo -> IO DefragmentationInfo
peek = Ptr DefragmentationInfo -> IO DefragmentationInfo
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DefragmentationInfo -> DefragmentationInfo -> IO ()
poke ptr :: Ptr DefragmentationInfo
ptr poked :: DefragmentationInfo
poked = Ptr DefragmentationInfo -> DefragmentationInfo -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DefragmentationInfo
ptr DefragmentationInfo
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DefragmentationInfo where
zero :: DefragmentationInfo
zero = ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32) -> DefragmentationInfo
DefragmentationInfo
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
data DefragmentationStats = DefragmentationStats
{
DefragmentationStats -> "lostAllocationCount" ::: Word64
bytesMoved :: DeviceSize
,
DefragmentationStats -> "lostAllocationCount" ::: Word64
bytesFreed :: DeviceSize
,
DefragmentationStats -> "memoryTypeIndex" ::: Word32
allocationsMoved :: Word32
,
DefragmentationStats -> "memoryTypeIndex" ::: Word32
deviceMemoryBlocksFreed :: Word32
}
deriving (Typeable, DefragmentationStats -> DefragmentationStats -> Bool
(DefragmentationStats -> DefragmentationStats -> Bool)
-> (DefragmentationStats -> DefragmentationStats -> Bool)
-> Eq DefragmentationStats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefragmentationStats -> DefragmentationStats -> Bool
$c/= :: DefragmentationStats -> DefragmentationStats -> Bool
== :: DefragmentationStats -> DefragmentationStats -> Bool
$c== :: DefragmentationStats -> DefragmentationStats -> Bool
Eq)
#if defined(GENERIC_INSTANCES)
deriving instance Generic (DefragmentationStats)
#endif
deriving instance Show DefragmentationStats
instance ToCStruct DefragmentationStats where
withCStruct :: DefragmentationStats -> (Ptr DefragmentationStats -> IO b) -> IO b
withCStruct x :: DefragmentationStats
x f :: Ptr DefragmentationStats -> IO b
f = Int -> Int -> (Ptr DefragmentationStats -> IO b) -> IO b
forall a b. Int -> Int -> (Ptr a -> IO b) -> IO b
allocaBytesAligned 24 8 ((Ptr DefragmentationStats -> IO b) -> IO b)
-> (Ptr DefragmentationStats -> IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ \p :: Ptr DefragmentationStats
p -> Ptr DefragmentationStats -> DefragmentationStats -> IO b -> IO b
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DefragmentationStats
p DefragmentationStats
x (Ptr DefragmentationStats -> IO b
f Ptr DefragmentationStats
p)
pokeCStruct :: Ptr DefragmentationStats -> DefragmentationStats -> IO b -> IO b
pokeCStruct p :: Ptr DefragmentationStats
p DefragmentationStats{..} f :: IO b
f = do
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
bytesMoved)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
bytesFreed)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
allocationsMoved)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
deviceMemoryBlocksFreed)
IO b
f
cStructSize :: Int
cStructSize = 24
cStructAlignment :: Int
cStructAlignment = 8
pokeZeroCStruct :: Ptr DefragmentationStats -> IO b -> IO b
pokeZeroCStruct p :: Ptr DefragmentationStats
p f :: IO b
f = do
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize)) ("lostAllocationCount" ::: Word64
forall a. Zero a => a
zero)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
Ptr ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32)) ("memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero)
IO b
f
instance FromCStruct DefragmentationStats where
peekCStruct :: Ptr DefragmentationStats -> IO DefragmentationStats
peekCStruct p :: Ptr DefragmentationStats
p = do
"lostAllocationCount" ::: Word64
bytesMoved <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0 :: Ptr DeviceSize))
"lostAllocationCount" ::: Word64
bytesFreed <- Ptr ("lostAllocationCount" ::: Word64)
-> IO ("lostAllocationCount" ::: Word64)
forall a. Storable a => Ptr a -> IO a
peek @DeviceSize ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("lostAllocationCount" ::: Word64)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8 :: Ptr DeviceSize))
"memoryTypeIndex" ::: Word32
allocationsMoved <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16 :: Ptr Word32))
"memoryTypeIndex" ::: Word32
deviceMemoryBlocksFreed <- Ptr ("memoryTypeIndex" ::: Word32)
-> IO ("memoryTypeIndex" ::: Word32)
forall a. Storable a => Ptr a -> IO a
peek @Word32 ((Ptr DefragmentationStats
p Ptr DefragmentationStats
-> Int -> Ptr ("memoryTypeIndex" ::: Word32)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20 :: Ptr Word32))
DefragmentationStats -> IO DefragmentationStats
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DefragmentationStats -> IO DefragmentationStats)
-> DefragmentationStats -> IO DefragmentationStats
forall a b. (a -> b) -> a -> b
$ ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32)
-> DefragmentationStats
DefragmentationStats
"lostAllocationCount" ::: Word64
bytesMoved "lostAllocationCount" ::: Word64
bytesFreed "memoryTypeIndex" ::: Word32
allocationsMoved "memoryTypeIndex" ::: Word32
deviceMemoryBlocksFreed
instance Storable DefragmentationStats where
sizeOf :: DefragmentationStats -> Int
sizeOf ~DefragmentationStats
_ = 24
alignment :: DefragmentationStats -> Int
alignment ~DefragmentationStats
_ = 8
peek :: Ptr DefragmentationStats -> IO DefragmentationStats
peek = Ptr DefragmentationStats -> IO DefragmentationStats
forall a. FromCStruct a => Ptr a -> IO a
peekCStruct
poke :: Ptr DefragmentationStats -> DefragmentationStats -> IO ()
poke ptr :: Ptr DefragmentationStats
ptr poked :: DefragmentationStats
poked = Ptr DefragmentationStats -> DefragmentationStats -> IO () -> IO ()
forall a b. ToCStruct a => Ptr a -> a -> IO b -> IO b
pokeCStruct Ptr DefragmentationStats
ptr DefragmentationStats
poked (() -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
instance Zero DefragmentationStats where
zero :: DefragmentationStats
zero = ("lostAllocationCount" ::: Word64)
-> ("lostAllocationCount" ::: Word64)
-> ("memoryTypeIndex" ::: Word32)
-> ("memoryTypeIndex" ::: Word32)
-> DefragmentationStats
DefragmentationStats
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"lostAllocationCount" ::: Word64
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero
"memoryTypeIndex" ::: Word32
forall a. Zero a => a
zero