Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides an orphan instance of PrimBytes
for VulkanMarshalPrim
structures.
This enables them to be stored in DataFrames
from easytensor
package.
Thanks to internal structure of Vulkan structures, they can be manipulated
inside DataFrames in a very efficient way (just by copying byte arrays).
However, original DataFrames
are based on unpinned arrays;
functions here check this and copy data to new pinned arrays if needed.
In addition to the orphan instance, this module provides a few handy helper functions.
Synopsis
- setVec :: forall fname x t. (FieldType fname x ~ t, PrimBytes t, KnownDim (FieldArrayLength fname x), CanWriteFieldArray fname x) => Vector t (FieldArrayLength fname x) -> CreateVkStruct x '[fname] ()
- getVec :: forall fname x t. (FieldType fname x ~ t, PrimBytes t, KnownDim (FieldArrayLength fname x), CanReadFieldArray fname x) => x -> Vector t (FieldArrayLength fname x)
- fillDataFrame :: forall a. PrimBytes a => Word -> (Ptr a -> IO ()) -> IO (Vector a (XN 0))
- withDFPtr :: forall (a :: Type) (ds :: [Nat]) (b :: Type). (PrimBytes a, Dimensions ds) => DataFrame a ds -> (Ptr a -> IO b) -> IO b
- setDFRef :: forall fname x a (ds :: [Nat]). (CanWriteField fname x, FieldType fname x ~ Ptr a, PrimBytes a, Dimensions ds) => DataFrame a ds -> CreateVkStruct x '[fname] ()
Documentation
setVec :: forall fname x t. (FieldType fname x ~ t, PrimBytes t, KnownDim (FieldArrayLength fname x), CanWriteFieldArray fname x) => Vector t (FieldArrayLength fname x) -> CreateVkStruct x '[fname] () Source #
Write an array of values in one go.
getVec :: forall fname x t. (FieldType fname x ~ t, PrimBytes t, KnownDim (FieldArrayLength fname x), CanReadFieldArray fname x) => x -> Vector t (FieldArrayLength fname x) Source #
Get an array of values, possibly without copying (if vector implementation allows).
fillDataFrame :: forall a. PrimBytes a => Word -> (Ptr a -> IO ()) -> IO (Vector a (XN 0)) Source #
Given the number of elements, create a new pinned DataFrame and initialize it using the provided function.
The argument function is called one time with a Ptr
pointing to the
beginning of a contiguous array.
This array is converted into a dataframe, possibly without copying.
It is safe to pass result of this function to withDFPtr
.
withDFPtr :: forall (a :: Type) (ds :: [Nat]) (b :: Type). (PrimBytes a, Dimensions ds) => DataFrame a ds -> (Ptr a -> IO b) -> IO b Source #
Run some operation with a pointer to the first item in the frame. All items of the frame are kept in a contiguous memory area accessed by that pointer.
The function attempts to get an underlying ByteArray#
without data copy;
otherwise, it creates a new pinned ByteArray#
and passes a pointer to it.
Therefore:
- Sometimes,
Ptr a
points to the original DF; sometimes, to a copied one. - If the original DF is based on unpinned
ByteArray#
, using this performs a copy anyway.
setDFRef :: forall fname x a (ds :: [Nat]). (CanWriteField fname x, FieldType fname x ~ Ptr a, PrimBytes a, Dimensions ds) => DataFrame a ds -> CreateVkStruct x '[fname] () Source #
A variant of setVkRef
that writes a pointer to a contiguous array of
structures.
Write a pointer to a vulkan structure - member of current structure and make sure the member exists as long as this structure exists.
Prefer this function to using unsafePtr a
, because the latter
does not keep the dependency information in GC, which results in
member structure being garbage-collected and the reference being invalid.
Orphan instances
VulkanMarshal (VkStruct a) => PrimBytes (VkStruct a) Source # | |
type PrimFields (VkStruct a) :: [Symbol] # getBytes :: VkStruct a -> ByteArray# # getBytesPinned :: VkStruct a -> ByteArray# # fromBytes :: Int# -> ByteArray# -> VkStruct a # readBytes :: MutableByteArray# s -> Int# -> State# s -> (# State# s, VkStruct a #) # writeBytes :: MutableByteArray# s -> Int# -> VkStruct a -> State# s -> State# s # readAddr :: Addr# -> State# s -> (# State# s, VkStruct a #) # writeAddr :: VkStruct a -> Addr# -> State# s -> State# s # byteSize :: VkStruct a -> Int# # byteAlign :: VkStruct a -> Int# # byteOffset :: VkStruct a -> Int# # byteFieldOffset :: forall (name :: Symbol). (Elem name (PrimFields (VkStruct a)), KnownSymbol name) => Proxy# name -> VkStruct a -> Int# # indexArray :: ByteArray# -> Int# -> VkStruct a # readArray :: MutableByteArray# s -> Int# -> State# s -> (# State# s, VkStruct a #) # writeArray :: MutableByteArray# s -> Int# -> VkStruct a -> State# s -> State# s # |