easytensor-vulkan-2.0.0.0: Use easytensor with vulkan-api.

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Marshal.Create.DataFrame

Contents

Description

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

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 a. (FieldType fname x ~ t, PrimBytes t, KnownDim (FieldArrayLength fname x), CanReadFieldArray fname x, x ~ VulkanStruct a) => 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 :: VulkanDataFrame a 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. (CanWriteField fname x, FieldType fname x ~ Ptr a, VulkanDataFrame a 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.

Helpers

class VulkanDataFrame a (ds :: [k]) where Source #

Methods

frameToVkData :: DataFrame a ds -> VkDataFrame a ds Source #

Construct a new VkDataFrame possibly without copying. It performs no copy if the DataFrame implementation is a pinned ByteArray#.

vkDataToFrame :: Dims ds -> VkDataFrame a ds -> DataFrame a ds Source #

Construct a new (pinned if implementation allows) DataFrame from VK data, possibly without copying.

Note, this is a user responsibility to check if the real size of VkDataFrame and the dimensionality ds agree.

Instances
(PrimBytes a, Dimensions ds) => VulkanDataFrame (a :: Type) (ds :: [Nat]) Source # 
Instance details

Defined in Graphics.Vulkan.Marshal.Create.DataFrame

(PrimBytes a, All KnownXNatType ds) => VulkanDataFrame (a :: Type) (ds :: [XNat]) Source # 
Instance details

Defined in Graphics.Vulkan.Marshal.Create.DataFrame

type VkDataFrame (t :: l) (ds :: [k]) = VulkanStruct (DataFrame t ds) Source #

Special data type used to provide VulkanMarshal instance for DataFrames. It is guaranteed to be pinned.

Orphan instances

Storable (VulkanStruct a) => PrimBytes (VulkanStruct a) Source # 
Instance details

Associated Types

type PrimFields (VulkanStruct a) :: [Symbol] #

PrimBytes (DataFrame t ds) => Storable (VkDataFrame t ds) Source # 
Instance details

Methods

sizeOf :: VkDataFrame t ds -> Int #

alignment :: VkDataFrame t ds -> Int #

peekElemOff :: Ptr (VkDataFrame t ds) -> Int -> IO (VkDataFrame t ds) #

pokeElemOff :: Ptr (VkDataFrame t ds) -> Int -> VkDataFrame t ds -> IO () #

peekByteOff :: Ptr b -> Int -> IO (VkDataFrame t ds) #

pokeByteOff :: Ptr b -> Int -> VkDataFrame t ds -> IO () #

peek :: Ptr (VkDataFrame t ds) -> IO (VkDataFrame t ds) #

poke :: Ptr (VkDataFrame t ds) -> VkDataFrame t ds -> IO () #

PrimBytes (DataFrame t ds) => VulkanMarshal (VkDataFrame t ds) Source # 
Instance details

Associated Types

type StructFields (VkDataFrame t ds) :: [Symbol] #

type CUnionType (VkDataFrame t ds) :: Bool #

type ReturnedOnly (VkDataFrame t ds) :: Bool #

type StructExtends (VkDataFrame t ds) :: [Type] #