vulkan-api-1.1.3.0: Low-level low-overhead vulkan api bindings

Safe HaskellNone
LanguageHaskell2010

Graphics.Vulkan.Marshal.Create

Description

This module is not part of auto-generated code based on vk.xml. It is also not included into Vulkan. It just provides convenient helpers for creation of vulkan structures.

Synopsis

Documentation

data CreateVkStruct x fs a Source #

Safely fill-in a new vulkan structure

Instances

Monad (CreateVkStruct x fs) Source # 

Methods

(>>=) :: CreateVkStruct x fs a -> (a -> CreateVkStruct x fs b) -> CreateVkStruct x fs b #

(>>) :: CreateVkStruct x fs a -> CreateVkStruct x fs b -> CreateVkStruct x fs b #

return :: a -> CreateVkStruct x fs a #

fail :: String -> CreateVkStruct x fs a #

Functor (CreateVkStruct x fs) Source # 

Methods

fmap :: (a -> b) -> CreateVkStruct x fs a -> CreateVkStruct x fs b #

(<$) :: a -> CreateVkStruct x fs b -> CreateVkStruct x fs a #

Applicative (CreateVkStruct x fs) Source # 

Methods

pure :: a -> CreateVkStruct x fs a #

(<*>) :: CreateVkStruct x fs (a -> b) -> CreateVkStruct x fs a -> CreateVkStruct x fs b #

(*>) :: CreateVkStruct x fs a -> CreateVkStruct x fs b -> CreateVkStruct x fs b #

(<*) :: CreateVkStruct x fs a -> CreateVkStruct x fs b -> CreateVkStruct x fs a #

createVk :: (VulkanMarshal x, VulkanMarshalPrim x, HandleRemFields x fs) => CreateVkStruct x fs () -> x Source #

Create a vulkan structure.

Use smart creation functions like setVk, setStrRef, setListRef, etc to keep GC aware of references between dependent structures.

createVk produces at most one weak reference to a created structure with a set of haskell and C finalizers. These finalizers make sure all malloced memory is released and no managed memory gets purged too early.

(&*) :: CreateVkStruct x as () -> CreateVkStruct x bs () -> CreateVkStruct x (Union x as bs) () infixl 1 Source #

Combine multiple field writes.

set :: forall fname x. CanWriteField fname x => FieldType fname x -> CreateVkStruct x '[fname] () Source #

writeField wrapped into CreateVkStruct monad.

setAt :: forall fname i x. CanWriteFieldArray fname i x => FieldType fname x -> CreateVkStruct x '[fname] () Source #

writeFieldArray wrapped into CreateVkStruct monad.

setVk :: forall fname x afs a. (CanWriteField fname x, a ~ FieldType fname x, VulkanMarshal a, HandleRemFields a afs) => CreateVkStruct a afs () -> CreateVkStruct x '[fname] () Source #

Write fields of a member struct.

setVkRef :: forall fname x a. (CanWriteField fname x, FieldType fname x ~ Ptr a, VulkanMarshal a) => a -> CreateVkStruct x '[fname] () Source #

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.

setStr :: forall fname x. (CanWriteFieldArray fname 0 x, FieldType fname x ~ CChar) => String -> CreateVkStruct x '[fname] () Source #

Write a String into a vulkan struct in-place.

setStrRef :: forall fname x. (CanWriteField fname x, FieldType fname x ~ CString) => String -> CreateVkStruct x '[fname] () Source #

Allocate memory for a CString, store it, and write a pointer to it into vulkan structure.

This function also attaches a reliable finalizer to the vulkan struct, so that the allocated memory is freed when the structure is GCed.

setStrListRef :: forall fname x. (CanWriteField fname x, FieldType fname x ~ Ptr CString) => [String] -> CreateVkStruct x '[fname] () Source #

Allocate memory for an array of elements, store them, and write a pointer to the array into vulkan structure.

This function also attaches a reliable finalizer to the vulkan struct, so that the array memory is freed when the structure is GCed.

This function writes null pointer if used with an empty list.

setListRef :: forall fname x a. (CanWriteField fname x, FieldType fname x ~ Ptr a, Storable a) => [a] -> CreateVkStruct x '[fname] () Source #

Allocate memory for an array of elements, store them, and write a pointer to the array into vulkan structure.

This function also attaches a reliable finalizer to the vulkan struct, so that the array memory is freed when the structure is GCed.

This function writes null pointer if used with an empty list.

class SetOptionalFields x fs where Source #

Minimal complete definition

setOptionalFields

Instances

SetOptionalFields x ([] Symbol) Source # 
(SetOptionalFields x fs, FieldMustBeOptional f x, Storable (FieldType f x), HasField f x) => SetOptionalFields x ((:) Symbol f fs) Source # 

Methods

setOptionalFields :: CreateVkStruct x ((Symbol ': f) fs) () Source #

class CUnionType x ~ isUnion => HandleRemainingFields x fs isUnion where Source #

Notify user if some required fields are missing and fill in optional fields.

Minimal complete definition

handleRemFields

Instances

(SetOptionalFields x (Difference (StructFields x) fs), (~) Bool (CUnionType x) False) => HandleRemainingFields x fs False Source # 
(TypeError Constraint (SetUnionMsg x), (~) Bool (CUnionType x) True) => HandleRemainingFields x ([] Symbol) True Source # 
(TypeError Constraint (SetUnionMsg x), (~) Bool (CUnionType x) True) => HandleRemainingFields x ((:) Symbol a ((:) Symbol b fs)) True Source # 

Methods

handleRemFields :: CreateVkStruct x ((Symbol ': a) ((Symbol ': b) fs)) () Source #

(~) Bool (CUnionType x) True => HandleRemainingFields x ((:) Symbol f ([] Symbol)) True Source # 

type HandleRemFields x fs = HandleRemainingFields x fs (CUnionType x) Source #

Notify user if some required fields are missing.

unsafeIOCreate :: (Ptr x -> IO a) -> CreateVkStruct x fs a Source #

Unsafe perform arbitrary IO action with a pointer to data under construction. This is used to add more functionality to this monad.