| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
- data CreateVkStruct x (fs :: [Symbol]) a
- createVk :: forall a fs. (VulkanMarshal a, HandleRemFields a fs) => CreateVkStruct a fs () -> a
- (&*) :: CreateVkStruct x as () -> CreateVkStruct x bs () -> CreateVkStruct x (Union x as bs) ()
- set :: forall fname x. CanWriteField fname x => FieldType fname x -> CreateVkStruct x '[fname] ()
- setAt :: forall fname i x. (CanWriteFieldArray fname x, IndexInBounds fname i x, KnownNat i) => FieldType fname x -> CreateVkStruct x '[fname] ()
- setVk :: forall fname x afs a. (CanWriteField fname x, a ~ FieldType fname x, VulkanMarshal a, HandleRemFields a afs) => CreateVkStruct a afs () -> CreateVkStruct x '[fname] ()
- setVkRef :: forall fname x a. (CanWriteField fname x, FieldType fname x ~ Ptr a, VulkanMarshal a) => a -> CreateVkStruct x '[fname] ()
- setStr :: forall fname x. (CanWriteFieldArray fname x, FieldType fname x ~ CChar) => String -> CreateVkStruct x '[fname] ()
- setStrRef :: forall fname x. (CanWriteField fname x, FieldType fname x ~ CString) => String -> CreateVkStruct x '[fname] ()
- setStrListRef :: forall fname x. (CanWriteField fname x, FieldType fname x ~ Ptr CString) => [String] -> CreateVkStruct x '[fname] ()
- setStrListCountAndRef :: forall countfname listfname x. (CanWriteField countfname x, CanWriteField listfname x, FieldType countfname x ~ Word32, FieldType listfname x ~ Ptr CString) => [String] -> CreateVkStruct x (Union x '[countfname] '[listfname]) ()
- setListRef :: forall fname x a. (CanWriteField fname x, FieldType fname x ~ Ptr a, Storable a) => [a] -> CreateVkStruct x '[fname] ()
- setListCountAndRef :: forall countfname listfname x a. (CanWriteField countfname x, CanWriteField listfname x, FieldType countfname x ~ Word32, FieldType listfname x ~ Ptr a, Storable a) => [a] -> CreateVkStruct x (Union x '[countfname] '[listfname]) ()
- class SetOptionalFields (x :: Type) (fs :: [Symbol]) where
- setOptionalFields :: CreateVkStruct x fs ()
- class CUnionType x ~ isUnion => HandleRemainingFields (x :: Type) (fs :: [Symbol]) (isUnion :: Bool) where
- handleRemFields :: CreateVkStruct x fs ()
- type HandleRemFields x fs = HandleRemainingFields x fs (CUnionType x)
- unsafeIOCreate :: (Ptr x -> IO a) -> CreateVkStruct x fs a
Documentation
data CreateVkStruct x (fs :: [Symbol]) a Source #
Safely fill-in a new vulkan structure
Instances
| Monad (CreateVkStruct x fs) Source # | |
Defined in Graphics.Vulkan.Marshal.Create 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 # | |
| Functor (CreateVkStruct x fs) Source # | |
Defined in Graphics.Vulkan.Marshal.Create 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 # | |
Defined in Graphics.Vulkan.Marshal.Create Methods pure :: a -> CreateVkStruct x fs a # (<*>) :: CreateVkStruct x fs (a -> b) -> CreateVkStruct x fs a -> CreateVkStruct x fs b # liftA2 :: (a -> b -> c) -> CreateVkStruct x fs a -> CreateVkStruct x fs b -> CreateVkStruct x fs c # (*>) :: 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 :: forall a fs. (VulkanMarshal a, HandleRemFields a fs) => CreateVkStruct a fs () -> a 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 x, IndexInBounds fname i x, KnownNat i) => 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 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.
setStrListCountAndRef :: forall countfname listfname x. (CanWriteField countfname x, CanWriteField listfname x, FieldType countfname x ~ Word32, FieldType listfname x ~ Ptr CString) => [String] -> CreateVkStruct x (Union x '[countfname] '[listfname]) () Source #
Equivalent to set on a count field and setStrListRef on a corresponding list field,
where the count is set to the length of the 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.
setListCountAndRef :: forall countfname listfname x a. (CanWriteField countfname x, CanWriteField listfname x, FieldType countfname x ~ Word32, FieldType listfname x ~ Ptr a, Storable a) => [a] -> CreateVkStruct x (Union x '[countfname] '[listfname]) () Source #
Equivalent to set on a count field and setListRef on a corresponding list field,
where the count is set to the length of the list.
class SetOptionalFields (x :: Type) (fs :: [Symbol]) where Source #
Methods
setOptionalFields :: CreateVkStruct x fs () Source #
Instances
| SetOptionalFields x ('[] :: [Symbol]) Source # | |
Defined in Graphics.Vulkan.Marshal.Create Methods setOptionalFields :: CreateVkStruct x '[] () Source # | |
| (SetOptionalFields x fs, FieldMustBeOptional f x, Storable (FieldType f x), HasField f x) => SetOptionalFields x (f ': fs) Source # | |
Defined in Graphics.Vulkan.Marshal.Create Methods setOptionalFields :: CreateVkStruct x (f ': fs) () Source # | |
class CUnionType x ~ isUnion => HandleRemainingFields (x :: Type) (fs :: [Symbol]) (isUnion :: Bool) where Source #
Notify user if some required fields are missing and fill in optional fields.
Methods
handleRemFields :: CreateVkStruct x fs () Source #
Instances
| (SetOptionalFields x (Difference (StructFieldNames x) fs), CUnionType x ~ 'False) => HandleRemainingFields x fs 'False Source # | |
Defined in Graphics.Vulkan.Marshal.Create Methods handleRemFields :: CreateVkStruct x fs () Source # | |
| (TypeError (SetUnionMsg x) :: Constraint, CUnionType x ~ 'True) => HandleRemainingFields x ('[] :: [Symbol]) 'True Source # | |
Defined in Graphics.Vulkan.Marshal.Create Methods handleRemFields :: CreateVkStruct x '[] () Source # | |
| (TypeError (SetUnionMsg x) :: Constraint, CUnionType x ~ 'True) => HandleRemainingFields x (a ': (b ': fs)) 'True Source # | |
Defined in Graphics.Vulkan.Marshal.Create Methods handleRemFields :: CreateVkStruct x (a ': (b ': fs)) () Source # | |
| CUnionType x ~ 'True => HandleRemainingFields x '[f] 'True Source # | |
Defined in Graphics.Vulkan.Marshal.Create Methods handleRemFields :: CreateVkStruct x '[f] () 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.